{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A @GSocket@ is a low-level networking primitive. It is a more or less
-- direct mapping of the BSD socket API in a portable GObject based API.
-- It supports both the UNIX socket implementations and winsock2 on Windows.
-- 
-- @GSocket@ is the platform independent base upon which the higher level
-- network primitives are based. Applications are not typically meant to
-- use it directly, but rather through classes like t'GI.Gio.Objects.SocketClient.SocketClient',
-- t'GI.Gio.Objects.SocketService.SocketService' and t'GI.Gio.Objects.SocketConnection.SocketConnection'. However there may
-- be cases where direct use of @GSocket@ is useful.
-- 
-- @GSocket@ implements the t'GI.Gio.Interfaces.Initable.Initable' interface, so if it is manually
-- constructed by e.g. t'GI.GObject.Objects.Object.Object'.@/new/@() you must call
-- 'GI.Gio.Interfaces.Initable.initableInit' and check the results before using the object.
-- This is done automatically in 'GI.Gio.Objects.Socket.socketNew' and
-- 'GI.Gio.Objects.Socket.socketNewFromFd', so these functions can return @NULL@.
-- 
-- Sockets operate in two general modes, blocking or non-blocking. When
-- in blocking mode all operations (which don’t take an explicit blocking
-- parameter) block until the requested operation
-- is finished or there is an error. In non-blocking mode all calls that
-- would block return immediately with a @G_IO_ERROR_WOULD_BLOCK@ error.
-- To know when a call would successfully run you can call
-- 'GI.Gio.Objects.Socket.socketConditionCheck', or 'GI.Gio.Objects.Socket.socketConditionWait'.
-- You can also use t'GI.Gio.Objects.Socket.Socket'.@/create_source/@() and attach it to a
-- [type/@gLib@/.MainContext] to get callbacks when I\/O is possible.
-- Note that all sockets are always set to non blocking mode in the system, and
-- blocking mode is emulated in @GSocket@.
-- 
-- When working in non-blocking mode applications should always be able to
-- handle getting a @G_IO_ERROR_WOULD_BLOCK@ error even when some other
-- function said that I\/O was possible. This can easily happen in case
-- of a race condition in the application, but it can also happen for other
-- reasons. For instance, on Windows a socket is always seen as writable
-- until a write returns @G_IO_ERROR_WOULD_BLOCK@.
-- 
-- @GSocket@s can be either connection oriented or datagram based.
-- For connection oriented types you must first establish a connection by
-- either connecting to an address or accepting a connection from another
-- address. For connectionless socket types the target\/source address is
-- specified or received in each I\/O operation.
-- 
-- All socket file descriptors are set to be close-on-exec.
-- 
-- Note that creating a @GSocket@ causes the signal @SIGPIPE@ to be
-- ignored for the remainder of the program. If you are writing a
-- command-line utility that uses @GSocket@, you may need to take into
-- account the fact that your program will not automatically be killed
-- if it tries to write to @stdout@ after it has been closed.
-- 
-- Like most other APIs in GLib, @GSocket@ is not inherently thread safe. To use
-- a @GSocket@ concurrently from multiple threads, you must implement your own
-- locking.
-- 
-- == Nagle’s algorithm
-- 
-- Since GLib 2.80, @GSocket@ will automatically set the @TCP_NODELAY@ option on
-- all @G_SOCKET_TYPE_STREAM@ sockets. This disables
-- <https://en.wikipedia.org/wiki/Nagle%27s_algorithm Nagle’s algorithm> as it
-- typically does more harm than good on modern networks.
-- 
-- If your application needs Nagle’s algorithm enabled, call
-- 'GI.Gio.Objects.Socket.socketSetOption' after constructing a @GSocket@ to enable it:
-- 
-- === /c code/
-- >socket = g_socket_new (…, G_SOCKET_TYPE_STREAM, …);
-- >if (socket != NULL)
-- >  {
-- >    g_socket_set_option (socket, IPPROTO_TCP, TCP_NODELAY, FALSE, &local_error);
-- >    // handle error if needed
-- >  }
-- 
-- 
-- /Since: 2.22/

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

module GI.Gio.Objects.Socket
    ( 

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


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [accept]("GI.Gio.Objects.Socket#g:method:accept"), [bind]("GI.Gio.Objects.Socket#g:method:bind"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [checkConnectResult]("GI.Gio.Objects.Socket#g:method:checkConnectResult"), [close]("GI.Gio.Objects.Socket#g:method:close"), [conditionCheck]("GI.Gio.Objects.Socket#g:method:conditionCheck"), [conditionTimedWait]("GI.Gio.Objects.Socket#g:method:conditionTimedWait"), [conditionWait]("GI.Gio.Objects.Socket#g:method:conditionWait"), [connect]("GI.Gio.Objects.Socket#g:method:connect"), [connectionFactoryCreateConnection]("GI.Gio.Objects.Socket#g:method:connectionFactoryCreateConnection"), [createSource]("GI.Gio.Interfaces.DatagramBased#g:method:createSource"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [init]("GI.Gio.Interfaces.Initable#g:method:init"), [isClosed]("GI.Gio.Objects.Socket#g:method:isClosed"), [isConnected]("GI.Gio.Objects.Socket#g:method:isConnected"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [joinMulticastGroup]("GI.Gio.Objects.Socket#g:method:joinMulticastGroup"), [joinMulticastGroupSsm]("GI.Gio.Objects.Socket#g:method:joinMulticastGroupSsm"), [leaveMulticastGroup]("GI.Gio.Objects.Socket#g:method:leaveMulticastGroup"), [leaveMulticastGroupSsm]("GI.Gio.Objects.Socket#g:method:leaveMulticastGroupSsm"), [listen]("GI.Gio.Objects.Socket#g:method:listen"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [receive]("GI.Gio.Objects.Socket#g:method:receive"), [receiveBytes]("GI.Gio.Objects.Socket#g:method:receiveBytes"), [receiveBytesFrom]("GI.Gio.Objects.Socket#g:method:receiveBytesFrom"), [receiveFrom]("GI.Gio.Objects.Socket#g:method:receiveFrom"), [receiveMessage]("GI.Gio.Objects.Socket#g:method:receiveMessage"), [receiveMessages]("GI.Gio.Objects.Socket#g:method:receiveMessages"), [receiveWithBlocking]("GI.Gio.Objects.Socket#g:method:receiveWithBlocking"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [send]("GI.Gio.Objects.Socket#g:method:send"), [sendMessage]("GI.Gio.Objects.Socket#g:method:sendMessage"), [sendMessageWithTimeout]("GI.Gio.Objects.Socket#g:method:sendMessageWithTimeout"), [sendMessages]("GI.Gio.Objects.Socket#g:method:sendMessages"), [sendTo]("GI.Gio.Objects.Socket#g:method:sendTo"), [sendWithBlocking]("GI.Gio.Objects.Socket#g:method:sendWithBlocking"), [shutdown]("GI.Gio.Objects.Socket#g:method:shutdown"), [speaksIpv4]("GI.Gio.Objects.Socket#g:method:speaksIpv4"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAvailableBytes]("GI.Gio.Objects.Socket#g:method:getAvailableBytes"), [getBlocking]("GI.Gio.Objects.Socket#g:method:getBlocking"), [getBroadcast]("GI.Gio.Objects.Socket#g:method:getBroadcast"), [getCredentials]("GI.Gio.Objects.Socket#g:method:getCredentials"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getFamily]("GI.Gio.Objects.Socket#g:method:getFamily"), [getFd]("GI.Gio.Objects.Socket#g:method:getFd"), [getKeepalive]("GI.Gio.Objects.Socket#g:method:getKeepalive"), [getListenBacklog]("GI.Gio.Objects.Socket#g:method:getListenBacklog"), [getLocalAddress]("GI.Gio.Objects.Socket#g:method:getLocalAddress"), [getMulticastLoopback]("GI.Gio.Objects.Socket#g:method:getMulticastLoopback"), [getMulticastTtl]("GI.Gio.Objects.Socket#g:method:getMulticastTtl"), [getOption]("GI.Gio.Objects.Socket#g:method:getOption"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getProtocol]("GI.Gio.Objects.Socket#g:method:getProtocol"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRemoteAddress]("GI.Gio.Objects.Socket#g:method:getRemoteAddress"), [getSocketType]("GI.Gio.Objects.Socket#g:method:getSocketType"), [getTimeout]("GI.Gio.Objects.Socket#g:method:getTimeout"), [getTtl]("GI.Gio.Objects.Socket#g:method:getTtl").
-- 
-- ==== Setters
-- [setBlocking]("GI.Gio.Objects.Socket#g:method:setBlocking"), [setBroadcast]("GI.Gio.Objects.Socket#g:method:setBroadcast"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setKeepalive]("GI.Gio.Objects.Socket#g:method:setKeepalive"), [setListenBacklog]("GI.Gio.Objects.Socket#g:method:setListenBacklog"), [setMulticastLoopback]("GI.Gio.Objects.Socket#g:method:setMulticastLoopback"), [setMulticastTtl]("GI.Gio.Objects.Socket#g:method:setMulticastTtl"), [setOption]("GI.Gio.Objects.Socket#g:method:setOption"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setTimeout]("GI.Gio.Objects.Socket#g:method:setTimeout"), [setTtl]("GI.Gio.Objects.Socket#g:method:setTtl").

#if defined(ENABLE_OVERLOADING)
    ResolveSocketMethod                     ,
#endif

-- ** accept #method:accept#

#if defined(ENABLE_OVERLOADING)
    SocketAcceptMethodInfo                  ,
#endif
    socketAccept                            ,


-- ** bind #method:bind#

#if defined(ENABLE_OVERLOADING)
    SocketBindMethodInfo                    ,
#endif
    socketBind                              ,


-- ** checkConnectResult #method:checkConnectResult#

#if defined(ENABLE_OVERLOADING)
    SocketCheckConnectResultMethodInfo      ,
#endif
    socketCheckConnectResult                ,


-- ** close #method:close#

#if defined(ENABLE_OVERLOADING)
    SocketCloseMethodInfo                   ,
#endif
    socketClose                             ,


-- ** conditionCheck #method:conditionCheck#

#if defined(ENABLE_OVERLOADING)
    SocketConditionCheckMethodInfo          ,
#endif
    socketConditionCheck                    ,


-- ** conditionTimedWait #method:conditionTimedWait#

#if defined(ENABLE_OVERLOADING)
    SocketConditionTimedWaitMethodInfo      ,
#endif
    socketConditionTimedWait                ,


-- ** conditionWait #method:conditionWait#

#if defined(ENABLE_OVERLOADING)
    SocketConditionWaitMethodInfo           ,
#endif
    socketConditionWait                     ,


-- ** connect #method:connect#

#if defined(ENABLE_OVERLOADING)
    SocketConnectMethodInfo                 ,
#endif
    socketConnect                           ,


-- ** connectionFactoryCreateConnection #method:connectionFactoryCreateConnection#

#if defined(ENABLE_OVERLOADING)
    SocketConnectionFactoryCreateConnectionMethodInfo,
#endif
    socketConnectionFactoryCreateConnection ,


-- ** getAvailableBytes #method:getAvailableBytes#

#if defined(ENABLE_OVERLOADING)
    SocketGetAvailableBytesMethodInfo       ,
#endif
    socketGetAvailableBytes                 ,


-- ** getBlocking #method:getBlocking#

#if defined(ENABLE_OVERLOADING)
    SocketGetBlockingMethodInfo             ,
#endif
    socketGetBlocking                       ,


-- ** getBroadcast #method:getBroadcast#

#if defined(ENABLE_OVERLOADING)
    SocketGetBroadcastMethodInfo            ,
#endif
    socketGetBroadcast                      ,


-- ** getCredentials #method:getCredentials#

#if defined(ENABLE_OVERLOADING)
    SocketGetCredentialsMethodInfo          ,
#endif
    socketGetCredentials                    ,


-- ** getFamily #method:getFamily#

#if defined(ENABLE_OVERLOADING)
    SocketGetFamilyMethodInfo               ,
#endif
    socketGetFamily                         ,


-- ** getFd #method:getFd#

#if defined(ENABLE_OVERLOADING)
    SocketGetFdMethodInfo                   ,
#endif
    socketGetFd                             ,


-- ** getKeepalive #method:getKeepalive#

#if defined(ENABLE_OVERLOADING)
    SocketGetKeepaliveMethodInfo            ,
#endif
    socketGetKeepalive                      ,


-- ** getListenBacklog #method:getListenBacklog#

#if defined(ENABLE_OVERLOADING)
    SocketGetListenBacklogMethodInfo        ,
#endif
    socketGetListenBacklog                  ,


-- ** getLocalAddress #method:getLocalAddress#

#if defined(ENABLE_OVERLOADING)
    SocketGetLocalAddressMethodInfo         ,
#endif
    socketGetLocalAddress                   ,


-- ** getMulticastLoopback #method:getMulticastLoopback#

#if defined(ENABLE_OVERLOADING)
    SocketGetMulticastLoopbackMethodInfo    ,
#endif
    socketGetMulticastLoopback              ,


-- ** getMulticastTtl #method:getMulticastTtl#

#if defined(ENABLE_OVERLOADING)
    SocketGetMulticastTtlMethodInfo         ,
#endif
    socketGetMulticastTtl                   ,


-- ** getOption #method:getOption#

#if defined(ENABLE_OVERLOADING)
    SocketGetOptionMethodInfo               ,
#endif
    socketGetOption                         ,


-- ** getProtocol #method:getProtocol#

#if defined(ENABLE_OVERLOADING)
    SocketGetProtocolMethodInfo             ,
#endif
    socketGetProtocol                       ,


-- ** getRemoteAddress #method:getRemoteAddress#

#if defined(ENABLE_OVERLOADING)
    SocketGetRemoteAddressMethodInfo        ,
#endif
    socketGetRemoteAddress                  ,


-- ** getSocketType #method:getSocketType#

#if defined(ENABLE_OVERLOADING)
    SocketGetSocketTypeMethodInfo           ,
#endif
    socketGetSocketType                     ,


-- ** getTimeout #method:getTimeout#

#if defined(ENABLE_OVERLOADING)
    SocketGetTimeoutMethodInfo              ,
#endif
    socketGetTimeout                        ,


-- ** getTtl #method:getTtl#

#if defined(ENABLE_OVERLOADING)
    SocketGetTtlMethodInfo                  ,
#endif
    socketGetTtl                            ,


-- ** isClosed #method:isClosed#

#if defined(ENABLE_OVERLOADING)
    SocketIsClosedMethodInfo                ,
#endif
    socketIsClosed                          ,


-- ** isConnected #method:isConnected#

#if defined(ENABLE_OVERLOADING)
    SocketIsConnectedMethodInfo             ,
#endif
    socketIsConnected                       ,


-- ** joinMulticastGroup #method:joinMulticastGroup#

#if defined(ENABLE_OVERLOADING)
    SocketJoinMulticastGroupMethodInfo      ,
#endif
    socketJoinMulticastGroup                ,


-- ** joinMulticastGroupSsm #method:joinMulticastGroupSsm#

#if defined(ENABLE_OVERLOADING)
    SocketJoinMulticastGroupSsmMethodInfo   ,
#endif
    socketJoinMulticastGroupSsm             ,


-- ** leaveMulticastGroup #method:leaveMulticastGroup#

#if defined(ENABLE_OVERLOADING)
    SocketLeaveMulticastGroupMethodInfo     ,
#endif
    socketLeaveMulticastGroup               ,


-- ** leaveMulticastGroupSsm #method:leaveMulticastGroupSsm#

#if defined(ENABLE_OVERLOADING)
    SocketLeaveMulticastGroupSsmMethodInfo  ,
#endif
    socketLeaveMulticastGroupSsm            ,


-- ** listen #method:listen#

#if defined(ENABLE_OVERLOADING)
    SocketListenMethodInfo                  ,
#endif
    socketListen                            ,


-- ** new #method:new#

    socketNew                               ,


-- ** newFromFd #method:newFromFd#

    socketNewFromFd                         ,


-- ** receive #method:receive#

#if defined(ENABLE_OVERLOADING)
    SocketReceiveMethodInfo                 ,
#endif
    socketReceive                           ,


-- ** receiveBytes #method:receiveBytes#

#if defined(ENABLE_OVERLOADING)
    SocketReceiveBytesMethodInfo            ,
#endif
    socketReceiveBytes                      ,


-- ** receiveBytesFrom #method:receiveBytesFrom#

#if defined(ENABLE_OVERLOADING)
    SocketReceiveBytesFromMethodInfo        ,
#endif
    socketReceiveBytesFrom                  ,


-- ** receiveFrom #method:receiveFrom#

#if defined(ENABLE_OVERLOADING)
    SocketReceiveFromMethodInfo             ,
#endif
    socketReceiveFrom                       ,


-- ** receiveMessage #method:receiveMessage#

#if defined(ENABLE_OVERLOADING)
    SocketReceiveMessageMethodInfo          ,
#endif
    socketReceiveMessage                    ,


-- ** receiveMessages #method:receiveMessages#

#if defined(ENABLE_OVERLOADING)
    SocketReceiveMessagesMethodInfo         ,
#endif
    socketReceiveMessages                   ,


-- ** receiveWithBlocking #method:receiveWithBlocking#

#if defined(ENABLE_OVERLOADING)
    SocketReceiveWithBlockingMethodInfo     ,
#endif
    socketReceiveWithBlocking               ,


-- ** send #method:send#

#if defined(ENABLE_OVERLOADING)
    SocketSendMethodInfo                    ,
#endif
    socketSend                              ,


-- ** sendMessage #method:sendMessage#

#if defined(ENABLE_OVERLOADING)
    SocketSendMessageMethodInfo             ,
#endif
    socketSendMessage                       ,


-- ** sendMessageWithTimeout #method:sendMessageWithTimeout#

#if defined(ENABLE_OVERLOADING)
    SocketSendMessageWithTimeoutMethodInfo  ,
#endif
    socketSendMessageWithTimeout            ,


-- ** sendMessages #method:sendMessages#

#if defined(ENABLE_OVERLOADING)
    SocketSendMessagesMethodInfo            ,
#endif
    socketSendMessages                      ,


-- ** sendTo #method:sendTo#

#if defined(ENABLE_OVERLOADING)
    SocketSendToMethodInfo                  ,
#endif
    socketSendTo                            ,


-- ** sendWithBlocking #method:sendWithBlocking#

#if defined(ENABLE_OVERLOADING)
    SocketSendWithBlockingMethodInfo        ,
#endif
    socketSendWithBlocking                  ,


-- ** setBlocking #method:setBlocking#

#if defined(ENABLE_OVERLOADING)
    SocketSetBlockingMethodInfo             ,
#endif
    socketSetBlocking                       ,


-- ** setBroadcast #method:setBroadcast#

#if defined(ENABLE_OVERLOADING)
    SocketSetBroadcastMethodInfo            ,
#endif
    socketSetBroadcast                      ,


-- ** setKeepalive #method:setKeepalive#

#if defined(ENABLE_OVERLOADING)
    SocketSetKeepaliveMethodInfo            ,
#endif
    socketSetKeepalive                      ,


-- ** setListenBacklog #method:setListenBacklog#

#if defined(ENABLE_OVERLOADING)
    SocketSetListenBacklogMethodInfo        ,
#endif
    socketSetListenBacklog                  ,


-- ** setMulticastLoopback #method:setMulticastLoopback#

#if defined(ENABLE_OVERLOADING)
    SocketSetMulticastLoopbackMethodInfo    ,
#endif
    socketSetMulticastLoopback              ,


-- ** setMulticastTtl #method:setMulticastTtl#

#if defined(ENABLE_OVERLOADING)
    SocketSetMulticastTtlMethodInfo         ,
#endif
    socketSetMulticastTtl                   ,


-- ** setOption #method:setOption#

#if defined(ENABLE_OVERLOADING)
    SocketSetOptionMethodInfo               ,
#endif
    socketSetOption                         ,


-- ** setTimeout #method:setTimeout#

#if defined(ENABLE_OVERLOADING)
    SocketSetTimeoutMethodInfo              ,
#endif
    socketSetTimeout                        ,


-- ** setTtl #method:setTtl#

#if defined(ENABLE_OVERLOADING)
    SocketSetTtlMethodInfo                  ,
#endif
    socketSetTtl                            ,


-- ** shutdown #method:shutdown#

#if defined(ENABLE_OVERLOADING)
    SocketShutdownMethodInfo                ,
#endif
    socketShutdown                          ,


-- ** speaksIpv4 #method:speaksIpv4#

#if defined(ENABLE_OVERLOADING)
    SocketSpeaksIpv4MethodInfo              ,
#endif
    socketSpeaksIpv4                        ,




 -- * Properties


-- ** blocking #attr:blocking#
-- | Whether I\/O on this socket is blocking.
-- 
-- /Since: 2.22/

#if defined(ENABLE_OVERLOADING)
    SocketBlockingPropertyInfo              ,
#endif
    constructSocketBlocking                 ,
    getSocketBlocking                       ,
    setSocketBlocking                       ,
#if defined(ENABLE_OVERLOADING)
    socketBlocking                          ,
#endif


-- ** broadcast #attr:broadcast#
-- | Whether the socket should allow sending to broadcast addresses.
-- 
-- /Since: 2.32/

#if defined(ENABLE_OVERLOADING)
    SocketBroadcastPropertyInfo             ,
#endif
    constructSocketBroadcast                ,
    getSocketBroadcast                      ,
    setSocketBroadcast                      ,
#if defined(ENABLE_OVERLOADING)
    socketBroadcast                         ,
#endif


-- ** family #attr:family#
-- | The socket’s address family.
-- 
-- /Since: 2.22/

#if defined(ENABLE_OVERLOADING)
    SocketFamilyPropertyInfo                ,
#endif
    constructSocketFamily                   ,
    getSocketFamily                         ,
#if defined(ENABLE_OVERLOADING)
    socketFamily                            ,
#endif


-- ** fd #attr:fd#
-- | The socket’s file descriptor.
-- 
-- /Since: 2.22/

#if defined(ENABLE_OVERLOADING)
    SocketFdPropertyInfo                    ,
#endif
    constructSocketFd                       ,
    getSocketFd                             ,
#if defined(ENABLE_OVERLOADING)
    socketFd                                ,
#endif


-- ** keepalive #attr:keepalive#
-- | Whether to keep the connection alive by sending periodic pings.
-- 
-- /Since: 2.22/

#if defined(ENABLE_OVERLOADING)
    SocketKeepalivePropertyInfo             ,
#endif
    constructSocketKeepalive                ,
    getSocketKeepalive                      ,
    setSocketKeepalive                      ,
#if defined(ENABLE_OVERLOADING)
    socketKeepalive                         ,
#endif


-- ** listenBacklog #attr:listenBacklog#
-- | The number of outstanding connections in the listen queue.
-- 
-- /Since: 2.22/

#if defined(ENABLE_OVERLOADING)
    SocketListenBacklogPropertyInfo         ,
#endif
    constructSocketListenBacklog            ,
    getSocketListenBacklog                  ,
    setSocketListenBacklog                  ,
#if defined(ENABLE_OVERLOADING)
    socketListenBacklog                     ,
#endif


-- ** localAddress #attr:localAddress#
-- | The local address the socket is bound to.
-- 
-- /Since: 2.22/

#if defined(ENABLE_OVERLOADING)
    SocketLocalAddressPropertyInfo          ,
#endif
    getSocketLocalAddress                   ,
#if defined(ENABLE_OVERLOADING)
    socketLocalAddress                      ,
#endif


-- ** multicastLoopback #attr:multicastLoopback#
-- | Whether outgoing multicast packets loop back to the local host.
-- 
-- /Since: 2.32/

#if defined(ENABLE_OVERLOADING)
    SocketMulticastLoopbackPropertyInfo     ,
#endif
    constructSocketMulticastLoopback        ,
    getSocketMulticastLoopback              ,
    setSocketMulticastLoopback              ,
#if defined(ENABLE_OVERLOADING)
    socketMulticastLoopback                 ,
#endif


-- ** multicastTtl #attr:multicastTtl#
-- | Time-to-live out outgoing multicast packets
-- 
-- /Since: 2.32/

#if defined(ENABLE_OVERLOADING)
    SocketMulticastTtlPropertyInfo          ,
#endif
    constructSocketMulticastTtl             ,
    getSocketMulticastTtl                   ,
    setSocketMulticastTtl                   ,
#if defined(ENABLE_OVERLOADING)
    socketMulticastTtl                      ,
#endif


-- ** protocol #attr:protocol#
-- | The ID of the protocol to use, or @-1@ for unknown.
-- 
-- /Since: 2.22/

#if defined(ENABLE_OVERLOADING)
    SocketProtocolPropertyInfo              ,
#endif
    constructSocketProtocol                 ,
    getSocketProtocol                       ,
#if defined(ENABLE_OVERLOADING)
    socketProtocol                          ,
#endif


-- ** remoteAddress #attr:remoteAddress#
-- | The remote address the socket is connected to.
-- 
-- /Since: 2.22/

#if defined(ENABLE_OVERLOADING)
    SocketRemoteAddressPropertyInfo         ,
#endif
    getSocketRemoteAddress                  ,
#if defined(ENABLE_OVERLOADING)
    socketRemoteAddress                     ,
#endif


-- ** timeout #attr:timeout#
-- | The timeout in seconds on socket I\/O
-- 
-- /Since: 2.26/

#if defined(ENABLE_OVERLOADING)
    SocketTimeoutPropertyInfo               ,
#endif
    constructSocketTimeout                  ,
    getSocketTimeout                        ,
    setSocketTimeout                        ,
#if defined(ENABLE_OVERLOADING)
    socketTimeout                           ,
#endif


-- ** ttl #attr:ttl#
-- | Time-to-live for outgoing unicast packets
-- 
-- /Since: 2.32/

#if defined(ENABLE_OVERLOADING)
    SocketTtlPropertyInfo                   ,
#endif
    constructSocketTtl                      ,
    getSocketTtl                            ,
    setSocketTtl                            ,
#if defined(ENABLE_OVERLOADING)
    socketTtl                               ,
#endif


-- ** type #attr:type#
-- | The socket’s type.
-- 
-- /Since: 2.22/

#if defined(ENABLE_OVERLOADING)
    SocketTypePropertyInfo                  ,
#endif
    constructSocketType                     ,
    getSocketType                           ,
#if defined(ENABLE_OVERLOADING)
    socketType                              ,
#endif




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GLib.Flags as GLib.Flags
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.PollFD as GLib.PollFD
import qualified GI.GLib.Structs.Source as GLib.Source
import qualified GI.GObject.Callbacks as GObject.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.GObject.Structs.Parameter as GObject.Parameter
import qualified GI.Gio.Callbacks as Gio.Callbacks
import {-# SOURCE #-} qualified GI.Gio.Enums as Gio.Enums
import {-# SOURCE #-} qualified GI.Gio.Flags as Gio.Flags
import {-# SOURCE #-} qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import {-# SOURCE #-} qualified GI.Gio.Interfaces.DatagramBased as Gio.DatagramBased
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Initable as Gio.Initable
import {-# SOURCE #-} qualified GI.Gio.Interfaces.SocketConnectable as Gio.SocketConnectable
import {-# SOURCE #-} qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.Gio.Objects.Credentials as Gio.Credentials
import {-# SOURCE #-} qualified GI.Gio.Objects.IOStream as Gio.IOStream
import {-# SOURCE #-} qualified GI.Gio.Objects.InetAddress as Gio.InetAddress
import {-# SOURCE #-} qualified GI.Gio.Objects.InputStream as Gio.InputStream
import {-# SOURCE #-} qualified GI.Gio.Objects.OutputStream as Gio.OutputStream
import {-# SOURCE #-} qualified GI.Gio.Objects.SocketAddress as Gio.SocketAddress
import {-# SOURCE #-} qualified GI.Gio.Objects.SocketAddressEnumerator as Gio.SocketAddressEnumerator
import {-# SOURCE #-} qualified GI.Gio.Objects.SocketConnection as Gio.SocketConnection
import {-# SOURCE #-} qualified GI.Gio.Objects.SocketControlMessage as Gio.SocketControlMessage
import {-# SOURCE #-} qualified GI.Gio.Structs.InputMessage as Gio.InputMessage
import {-# SOURCE #-} qualified GI.Gio.Structs.InputVector as Gio.InputVector
import {-# SOURCE #-} qualified GI.Gio.Structs.OutputMessage as Gio.OutputMessage
import {-# SOURCE #-} qualified GI.Gio.Structs.OutputVector as Gio.OutputVector

#else
import qualified GI.GLib.Flags as GLib.Flags
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Enums as Gio.Enums
import {-# SOURCE #-} qualified GI.Gio.Interfaces.DatagramBased as Gio.DatagramBased
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Initable as Gio.Initable
import {-# SOURCE #-} qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.Gio.Objects.Credentials as Gio.Credentials
import {-# SOURCE #-} qualified GI.Gio.Objects.InetAddress as Gio.InetAddress
import {-# SOURCE #-} qualified GI.Gio.Objects.SocketAddress as Gio.SocketAddress
import {-# SOURCE #-} qualified GI.Gio.Objects.SocketConnection as Gio.SocketConnection
import {-# SOURCE #-} qualified GI.Gio.Objects.SocketControlMessage as Gio.SocketControlMessage
import {-# SOURCE #-} qualified GI.Gio.Structs.InputMessage as Gio.InputMessage
import {-# SOURCE #-} qualified GI.Gio.Structs.InputVector as Gio.InputVector
import {-# SOURCE #-} qualified GI.Gio.Structs.OutputMessage as Gio.OutputMessage
import {-# SOURCE #-} qualified GI.Gio.Structs.OutputVector as Gio.OutputVector

#endif

-- | Memory-managed wrapper type.
newtype Socket = Socket (SP.ManagedPtr Socket)
    deriving (Socket -> Socket -> Bool
(Socket -> Socket -> Bool)
-> (Socket -> Socket -> Bool) -> Eq Socket
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Socket -> Socket -> Bool
== :: Socket -> Socket -> Bool
$c/= :: Socket -> Socket -> Bool
/= :: Socket -> Socket -> Bool
Eq)

instance SP.ManagedPtrNewtype Socket where
    toManagedPtr :: Socket -> ManagedPtr Socket
toManagedPtr (Socket ManagedPtr Socket
p) = ManagedPtr Socket
p

foreign import ccall "g_socket_get_type"
    c_g_socket_get_type :: IO B.Types.GType

instance B.Types.TypedObject Socket where
    glibType :: IO GType
glibType = IO GType
c_g_socket_get_type

instance B.Types.GObject Socket

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

instance O.HasParentTypes Socket
type instance O.ParentTypes Socket = '[GObject.Object.Object, Gio.DatagramBased.DatagramBased, Gio.Initable.Initable]

-- | Cast to `Socket`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toSocket :: (MIO.MonadIO m, IsSocket o) => o -> m Socket
toSocket :: forall (m :: * -> *) o. (MonadIO m, IsSocket o) => o -> m Socket
toSocket = IO Socket -> m Socket
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Socket -> Socket
Socket

-- | Convert 'Socket' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe Socket) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_socket_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Socket -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Socket
P.Nothing = Ptr GValue -> Ptr Socket -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Socket
forall a. Ptr a
FP.nullPtr :: FP.Ptr Socket)
    gvalueSet_ Ptr GValue
gv (P.Just Socket
obj) = Socket -> (Ptr Socket -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Socket
obj (Ptr GValue -> Ptr Socket -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Socket)
gvalueGet_ Ptr GValue
gv = do
        ptr <- Ptr GValue -> IO (Ptr Socket)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Socket)
        if ptr /= FP.nullPtr
        then P.Just <$> B.ManagedPtr.newObject Socket ptr
        else return P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveSocketMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveSocketMethod "accept" o = SocketAcceptMethodInfo
    ResolveSocketMethod "bind" o = SocketBindMethodInfo
    ResolveSocketMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveSocketMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveSocketMethod "checkConnectResult" o = SocketCheckConnectResultMethodInfo
    ResolveSocketMethod "close" o = SocketCloseMethodInfo
    ResolveSocketMethod "conditionCheck" o = SocketConditionCheckMethodInfo
    ResolveSocketMethod "conditionTimedWait" o = SocketConditionTimedWaitMethodInfo
    ResolveSocketMethod "conditionWait" o = SocketConditionWaitMethodInfo
    ResolveSocketMethod "connect" o = SocketConnectMethodInfo
    ResolveSocketMethod "connectionFactoryCreateConnection" o = SocketConnectionFactoryCreateConnectionMethodInfo
    ResolveSocketMethod "createSource" o = Gio.DatagramBased.DatagramBasedCreateSourceMethodInfo
    ResolveSocketMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveSocketMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveSocketMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveSocketMethod "init" o = Gio.Initable.InitableInitMethodInfo
    ResolveSocketMethod "isClosed" o = SocketIsClosedMethodInfo
    ResolveSocketMethod "isConnected" o = SocketIsConnectedMethodInfo
    ResolveSocketMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveSocketMethod "joinMulticastGroup" o = SocketJoinMulticastGroupMethodInfo
    ResolveSocketMethod "joinMulticastGroupSsm" o = SocketJoinMulticastGroupSsmMethodInfo
    ResolveSocketMethod "leaveMulticastGroup" o = SocketLeaveMulticastGroupMethodInfo
    ResolveSocketMethod "leaveMulticastGroupSsm" o = SocketLeaveMulticastGroupSsmMethodInfo
    ResolveSocketMethod "listen" o = SocketListenMethodInfo
    ResolveSocketMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveSocketMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveSocketMethod "receive" o = SocketReceiveMethodInfo
    ResolveSocketMethod "receiveBytes" o = SocketReceiveBytesMethodInfo
    ResolveSocketMethod "receiveBytesFrom" o = SocketReceiveBytesFromMethodInfo
    ResolveSocketMethod "receiveFrom" o = SocketReceiveFromMethodInfo
    ResolveSocketMethod "receiveMessage" o = SocketReceiveMessageMethodInfo
    ResolveSocketMethod "receiveMessages" o = SocketReceiveMessagesMethodInfo
    ResolveSocketMethod "receiveWithBlocking" o = SocketReceiveWithBlockingMethodInfo
    ResolveSocketMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveSocketMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveSocketMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveSocketMethod "send" o = SocketSendMethodInfo
    ResolveSocketMethod "sendMessage" o = SocketSendMessageMethodInfo
    ResolveSocketMethod "sendMessageWithTimeout" o = SocketSendMessageWithTimeoutMethodInfo
    ResolveSocketMethod "sendMessages" o = SocketSendMessagesMethodInfo
    ResolveSocketMethod "sendTo" o = SocketSendToMethodInfo
    ResolveSocketMethod "sendWithBlocking" o = SocketSendWithBlockingMethodInfo
    ResolveSocketMethod "shutdown" o = SocketShutdownMethodInfo
    ResolveSocketMethod "speaksIpv4" o = SocketSpeaksIpv4MethodInfo
    ResolveSocketMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveSocketMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveSocketMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveSocketMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveSocketMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveSocketMethod "getAvailableBytes" o = SocketGetAvailableBytesMethodInfo
    ResolveSocketMethod "getBlocking" o = SocketGetBlockingMethodInfo
    ResolveSocketMethod "getBroadcast" o = SocketGetBroadcastMethodInfo
    ResolveSocketMethod "getCredentials" o = SocketGetCredentialsMethodInfo
    ResolveSocketMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveSocketMethod "getFamily" o = SocketGetFamilyMethodInfo
    ResolveSocketMethod "getFd" o = SocketGetFdMethodInfo
    ResolveSocketMethod "getKeepalive" o = SocketGetKeepaliveMethodInfo
    ResolveSocketMethod "getListenBacklog" o = SocketGetListenBacklogMethodInfo
    ResolveSocketMethod "getLocalAddress" o = SocketGetLocalAddressMethodInfo
    ResolveSocketMethod "getMulticastLoopback" o = SocketGetMulticastLoopbackMethodInfo
    ResolveSocketMethod "getMulticastTtl" o = SocketGetMulticastTtlMethodInfo
    ResolveSocketMethod "getOption" o = SocketGetOptionMethodInfo
    ResolveSocketMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveSocketMethod "getProtocol" o = SocketGetProtocolMethodInfo
    ResolveSocketMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveSocketMethod "getRemoteAddress" o = SocketGetRemoteAddressMethodInfo
    ResolveSocketMethod "getSocketType" o = SocketGetSocketTypeMethodInfo
    ResolveSocketMethod "getTimeout" o = SocketGetTimeoutMethodInfo
    ResolveSocketMethod "getTtl" o = SocketGetTtlMethodInfo
    ResolveSocketMethod "setBlocking" o = SocketSetBlockingMethodInfo
    ResolveSocketMethod "setBroadcast" o = SocketSetBroadcastMethodInfo
    ResolveSocketMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveSocketMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveSocketMethod "setKeepalive" o = SocketSetKeepaliveMethodInfo
    ResolveSocketMethod "setListenBacklog" o = SocketSetListenBacklogMethodInfo
    ResolveSocketMethod "setMulticastLoopback" o = SocketSetMulticastLoopbackMethodInfo
    ResolveSocketMethod "setMulticastTtl" o = SocketSetMulticastTtlMethodInfo
    ResolveSocketMethod "setOption" o = SocketSetOptionMethodInfo
    ResolveSocketMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveSocketMethod "setTimeout" o = SocketSetTimeoutMethodInfo
    ResolveSocketMethod "setTtl" o = SocketSetTtlMethodInfo
    ResolveSocketMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveSocketMethod t Socket, O.OverloadedMethod 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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveSocketMethod t Socket, O.OverloadedMethod info Socket p, R.HasField t Socket p) => R.HasField t Socket p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveSocketMethod t Socket, O.OverloadedMethodInfo info Socket) => OL.IsLabel t (O.MethodProxy info Socket) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

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

-- | Get the value of the “@blocking@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' socket #blocking
-- @
getSocketBlocking :: (MonadIO m, IsSocket o) => o -> m Bool
getSocketBlocking :: forall (m :: * -> *) o. (MonadIO m, IsSocket o) => o -> m Bool
getSocketBlocking o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"blocking"

-- | Set the value of the “@blocking@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' socket [ #blocking 'Data.GI.Base.Attributes.:=' value ]
-- @
setSocketBlocking :: (MonadIO m, IsSocket o) => o -> Bool -> m ()
setSocketBlocking :: forall (m :: * -> *) o.
(MonadIO m, IsSocket o) =>
o -> Bool -> m ()
setSocketBlocking o
obj Bool
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"blocking" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@blocking@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSocketBlocking :: (IsSocket o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructSocketBlocking :: forall o (m :: * -> *).
(IsSocket o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructSocketBlocking Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"blocking" Bool
val

#if defined(ENABLE_OVERLOADING)
data SocketBlockingPropertyInfo
instance AttrInfo SocketBlockingPropertyInfo where
    type AttrAllowedOps SocketBlockingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SocketBlockingPropertyInfo = IsSocket
    type AttrSetTypeConstraint SocketBlockingPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SocketBlockingPropertyInfo = (~) Bool
    type AttrTransferType SocketBlockingPropertyInfo = Bool
    type AttrGetType SocketBlockingPropertyInfo = Bool
    type AttrLabel SocketBlockingPropertyInfo = "blocking"
    type AttrOrigin SocketBlockingPropertyInfo = Socket
    attrGet = getSocketBlocking
    attrSet = setSocketBlocking
    attrTransfer _ v = do
        return v
    attrConstruct = constructSocketBlocking
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.blocking"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#g:attr:blocking"
        })
#endif

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

-- | Get the value of the “@broadcast@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' socket #broadcast
-- @
getSocketBroadcast :: (MonadIO m, IsSocket o) => o -> m Bool
getSocketBroadcast :: forall (m :: * -> *) o. (MonadIO m, IsSocket o) => o -> m Bool
getSocketBroadcast o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"broadcast"

-- | Set the value of the “@broadcast@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' socket [ #broadcast 'Data.GI.Base.Attributes.:=' value ]
-- @
setSocketBroadcast :: (MonadIO m, IsSocket o) => o -> Bool -> m ()
setSocketBroadcast :: forall (m :: * -> *) o.
(MonadIO m, IsSocket o) =>
o -> Bool -> m ()
setSocketBroadcast o
obj Bool
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"broadcast" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@broadcast@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSocketBroadcast :: (IsSocket o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructSocketBroadcast :: forall o (m :: * -> *).
(IsSocket o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructSocketBroadcast Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"broadcast" Bool
val

#if defined(ENABLE_OVERLOADING)
data SocketBroadcastPropertyInfo
instance AttrInfo SocketBroadcastPropertyInfo where
    type AttrAllowedOps SocketBroadcastPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SocketBroadcastPropertyInfo = IsSocket
    type AttrSetTypeConstraint SocketBroadcastPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SocketBroadcastPropertyInfo = (~) Bool
    type AttrTransferType SocketBroadcastPropertyInfo = Bool
    type AttrGetType SocketBroadcastPropertyInfo = Bool
    type AttrLabel SocketBroadcastPropertyInfo = "broadcast"
    type AttrOrigin SocketBroadcastPropertyInfo = Socket
    attrGet = getSocketBroadcast
    attrSet = setSocketBroadcast
    attrTransfer _ v = do
        return v
    attrConstruct = constructSocketBroadcast
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.broadcast"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#g:attr:broadcast"
        })
#endif

-- VVV Prop "family"
   -- Type: TInterface (Name {namespace = "Gio", name = "SocketFamily"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@family@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' socket #family
-- @
getSocketFamily :: (MonadIO m, IsSocket o) => o -> m Gio.Enums.SocketFamily
getSocketFamily :: forall (m :: * -> *) o.
(MonadIO m, IsSocket o) =>
o -> m SocketFamily
getSocketFamily o
obj = IO SocketFamily -> m SocketFamily
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO SocketFamily -> m SocketFamily)
-> IO SocketFamily -> m SocketFamily
forall a b. (a -> b) -> a -> b
$ o -> String -> IO SocketFamily
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"family"

-- | Construct a `GValueConstruct` with valid value for the “@family@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSocketFamily :: (IsSocket o, MIO.MonadIO m) => Gio.Enums.SocketFamily -> m (GValueConstruct o)
constructSocketFamily :: forall o (m :: * -> *).
(IsSocket o, MonadIO m) =>
SocketFamily -> m (GValueConstruct o)
constructSocketFamily SocketFamily
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> SocketFamily -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"family" SocketFamily
val

#if defined(ENABLE_OVERLOADING)
data SocketFamilyPropertyInfo
instance AttrInfo SocketFamilyPropertyInfo where
    type AttrAllowedOps SocketFamilyPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SocketFamilyPropertyInfo = IsSocket
    type AttrSetTypeConstraint SocketFamilyPropertyInfo = (~) Gio.Enums.SocketFamily
    type AttrTransferTypeConstraint SocketFamilyPropertyInfo = (~) Gio.Enums.SocketFamily
    type AttrTransferType SocketFamilyPropertyInfo = Gio.Enums.SocketFamily
    type AttrGetType SocketFamilyPropertyInfo = Gio.Enums.SocketFamily
    type AttrLabel SocketFamilyPropertyInfo = "family"
    type AttrOrigin SocketFamilyPropertyInfo = Socket
    attrGet = getSocketFamily
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructSocketFamily
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.family"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#g:attr:family"
        })
#endif

-- VVV Prop "fd"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@fd@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' socket #fd
-- @
getSocketFd :: (MonadIO m, IsSocket o) => o -> m Int32
getSocketFd :: forall (m :: * -> *) o. (MonadIO m, IsSocket o) => o -> m Int32
getSocketFd o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"fd"

-- | Construct a `GValueConstruct` with valid value for the “@fd@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSocketFd :: (IsSocket o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructSocketFd :: forall o (m :: * -> *).
(IsSocket o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructSocketFd Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"fd" Int32
val

#if defined(ENABLE_OVERLOADING)
data SocketFdPropertyInfo
instance AttrInfo SocketFdPropertyInfo where
    type AttrAllowedOps SocketFdPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SocketFdPropertyInfo = IsSocket
    type AttrSetTypeConstraint SocketFdPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint SocketFdPropertyInfo = (~) Int32
    type AttrTransferType SocketFdPropertyInfo = Int32
    type AttrGetType SocketFdPropertyInfo = Int32
    type AttrLabel SocketFdPropertyInfo = "fd"
    type AttrOrigin SocketFdPropertyInfo = Socket
    attrGet = getSocketFd
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructSocketFd
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.fd"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#g:attr:fd"
        })
#endif

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

-- | Get the value of the “@keepalive@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' socket #keepalive
-- @
getSocketKeepalive :: (MonadIO m, IsSocket o) => o -> m Bool
getSocketKeepalive :: forall (m :: * -> *) o. (MonadIO m, IsSocket o) => o -> m Bool
getSocketKeepalive o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"keepalive"

-- | Set the value of the “@keepalive@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' socket [ #keepalive 'Data.GI.Base.Attributes.:=' value ]
-- @
setSocketKeepalive :: (MonadIO m, IsSocket o) => o -> Bool -> m ()
setSocketKeepalive :: forall (m :: * -> *) o.
(MonadIO m, IsSocket o) =>
o -> Bool -> m ()
setSocketKeepalive o
obj Bool
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"keepalive" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@keepalive@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSocketKeepalive :: (IsSocket o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructSocketKeepalive :: forall o (m :: * -> *).
(IsSocket o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructSocketKeepalive Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"keepalive" Bool
val

#if defined(ENABLE_OVERLOADING)
data SocketKeepalivePropertyInfo
instance AttrInfo SocketKeepalivePropertyInfo where
    type AttrAllowedOps SocketKeepalivePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SocketKeepalivePropertyInfo = IsSocket
    type AttrSetTypeConstraint SocketKeepalivePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SocketKeepalivePropertyInfo = (~) Bool
    type AttrTransferType SocketKeepalivePropertyInfo = Bool
    type AttrGetType SocketKeepalivePropertyInfo = Bool
    type AttrLabel SocketKeepalivePropertyInfo = "keepalive"
    type AttrOrigin SocketKeepalivePropertyInfo = Socket
    attrGet = getSocketKeepalive
    attrSet = setSocketKeepalive
    attrTransfer _ v = do
        return v
    attrConstruct = constructSocketKeepalive
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.keepalive"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#g:attr:keepalive"
        })
#endif

-- VVV Prop "listen-backlog"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@listen-backlog@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' socket #listenBacklog
-- @
getSocketListenBacklog :: (MonadIO m, IsSocket o) => o -> m Int32
getSocketListenBacklog :: forall (m :: * -> *) o. (MonadIO m, IsSocket o) => o -> m Int32
getSocketListenBacklog o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"listen-backlog"

-- | Set the value of the “@listen-backlog@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' socket [ #listenBacklog 'Data.GI.Base.Attributes.:=' value ]
-- @
setSocketListenBacklog :: (MonadIO m, IsSocket o) => o -> Int32 -> m ()
setSocketListenBacklog :: forall (m :: * -> *) o.
(MonadIO m, IsSocket o) =>
o -> Int32 -> m ()
setSocketListenBacklog o
obj Int32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"listen-backlog" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@listen-backlog@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSocketListenBacklog :: (IsSocket o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructSocketListenBacklog :: forall o (m :: * -> *).
(IsSocket o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructSocketListenBacklog Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"listen-backlog" Int32
val

#if defined(ENABLE_OVERLOADING)
data SocketListenBacklogPropertyInfo
instance AttrInfo SocketListenBacklogPropertyInfo where
    type AttrAllowedOps SocketListenBacklogPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SocketListenBacklogPropertyInfo = IsSocket
    type AttrSetTypeConstraint SocketListenBacklogPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint SocketListenBacklogPropertyInfo = (~) Int32
    type AttrTransferType SocketListenBacklogPropertyInfo = Int32
    type AttrGetType SocketListenBacklogPropertyInfo = Int32
    type AttrLabel SocketListenBacklogPropertyInfo = "listen-backlog"
    type AttrOrigin SocketListenBacklogPropertyInfo = Socket
    attrGet = getSocketListenBacklog
    attrSet = setSocketListenBacklog
    attrTransfer _ v = do
        return v
    attrConstruct = constructSocketListenBacklog
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.listenBacklog"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#g:attr:listenBacklog"
        })
#endif

-- VVV Prop "local-address"
   -- Type: TInterface (Name {namespace = "Gio", name = "SocketAddress"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

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

#if defined(ENABLE_OVERLOADING)
data SocketLocalAddressPropertyInfo
instance AttrInfo SocketLocalAddressPropertyInfo where
    type AttrAllowedOps SocketLocalAddressPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SocketLocalAddressPropertyInfo = IsSocket
    type AttrSetTypeConstraint SocketLocalAddressPropertyInfo = (~) ()
    type AttrTransferTypeConstraint SocketLocalAddressPropertyInfo = (~) ()
    type AttrTransferType SocketLocalAddressPropertyInfo = ()
    type AttrGetType SocketLocalAddressPropertyInfo = (Maybe Gio.SocketAddress.SocketAddress)
    type AttrLabel SocketLocalAddressPropertyInfo = "local-address"
    type AttrOrigin SocketLocalAddressPropertyInfo = Socket
    attrGet = getSocketLocalAddress
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.localAddress"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#g:attr:localAddress"
        })
#endif

-- VVV Prop "multicast-loopback"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@multicast-loopback@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' socket #multicastLoopback
-- @
getSocketMulticastLoopback :: (MonadIO m, IsSocket o) => o -> m Bool
getSocketMulticastLoopback :: forall (m :: * -> *) o. (MonadIO m, IsSocket o) => o -> m Bool
getSocketMulticastLoopback o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"multicast-loopback"

-- | Set the value of the “@multicast-loopback@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' socket [ #multicastLoopback 'Data.GI.Base.Attributes.:=' value ]
-- @
setSocketMulticastLoopback :: (MonadIO m, IsSocket o) => o -> Bool -> m ()
setSocketMulticastLoopback :: forall (m :: * -> *) o.
(MonadIO m, IsSocket o) =>
o -> Bool -> m ()
setSocketMulticastLoopback o
obj Bool
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"multicast-loopback" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@multicast-loopback@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSocketMulticastLoopback :: (IsSocket o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructSocketMulticastLoopback :: forall o (m :: * -> *).
(IsSocket o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructSocketMulticastLoopback Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"multicast-loopback" Bool
val

#if defined(ENABLE_OVERLOADING)
data SocketMulticastLoopbackPropertyInfo
instance AttrInfo SocketMulticastLoopbackPropertyInfo where
    type AttrAllowedOps SocketMulticastLoopbackPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SocketMulticastLoopbackPropertyInfo = IsSocket
    type AttrSetTypeConstraint SocketMulticastLoopbackPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SocketMulticastLoopbackPropertyInfo = (~) Bool
    type AttrTransferType SocketMulticastLoopbackPropertyInfo = Bool
    type AttrGetType SocketMulticastLoopbackPropertyInfo = Bool
    type AttrLabel SocketMulticastLoopbackPropertyInfo = "multicast-loopback"
    type AttrOrigin SocketMulticastLoopbackPropertyInfo = Socket
    attrGet = getSocketMulticastLoopback
    attrSet = setSocketMulticastLoopback
    attrTransfer _ v = do
        return v
    attrConstruct = constructSocketMulticastLoopback
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.multicastLoopback"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#g:attr:multicastLoopback"
        })
#endif

-- VVV Prop "multicast-ttl"
   -- Type: TBasicType TUInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@multicast-ttl@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' socket #multicastTtl
-- @
getSocketMulticastTtl :: (MonadIO m, IsSocket o) => o -> m Word32
getSocketMulticastTtl :: forall (m :: * -> *) o. (MonadIO m, IsSocket o) => o -> m Word32
getSocketMulticastTtl o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"multicast-ttl"

-- | Set the value of the “@multicast-ttl@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' socket [ #multicastTtl 'Data.GI.Base.Attributes.:=' value ]
-- @
setSocketMulticastTtl :: (MonadIO m, IsSocket o) => o -> Word32 -> m ()
setSocketMulticastTtl :: forall (m :: * -> *) o.
(MonadIO m, IsSocket o) =>
o -> Word32 -> m ()
setSocketMulticastTtl o
obj Word32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"multicast-ttl" Word32
val

-- | Construct a `GValueConstruct` with valid value for the “@multicast-ttl@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSocketMulticastTtl :: (IsSocket o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructSocketMulticastTtl :: forall o (m :: * -> *).
(IsSocket o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructSocketMulticastTtl Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"multicast-ttl" Word32
val

#if defined(ENABLE_OVERLOADING)
data SocketMulticastTtlPropertyInfo
instance AttrInfo SocketMulticastTtlPropertyInfo where
    type AttrAllowedOps SocketMulticastTtlPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SocketMulticastTtlPropertyInfo = IsSocket
    type AttrSetTypeConstraint SocketMulticastTtlPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint SocketMulticastTtlPropertyInfo = (~) Word32
    type AttrTransferType SocketMulticastTtlPropertyInfo = Word32
    type AttrGetType SocketMulticastTtlPropertyInfo = Word32
    type AttrLabel SocketMulticastTtlPropertyInfo = "multicast-ttl"
    type AttrOrigin SocketMulticastTtlPropertyInfo = Socket
    attrGet = getSocketMulticastTtl
    attrSet = setSocketMulticastTtl
    attrTransfer _ v = do
        return v
    attrConstruct = constructSocketMulticastTtl
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.multicastTtl"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#g:attr:multicastTtl"
        })
#endif

-- VVV Prop "protocol"
   -- Type: TInterface (Name {namespace = "Gio", name = "SocketProtocol"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@protocol@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' socket #protocol
-- @
getSocketProtocol :: (MonadIO m, IsSocket o) => o -> m Gio.Enums.SocketProtocol
getSocketProtocol :: forall (m :: * -> *) o.
(MonadIO m, IsSocket o) =>
o -> m SocketProtocol
getSocketProtocol o
obj = IO SocketProtocol -> m SocketProtocol
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO SocketProtocol -> m SocketProtocol)
-> IO SocketProtocol -> m SocketProtocol
forall a b. (a -> b) -> a -> b
$ o -> String -> IO SocketProtocol
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"protocol"

-- | Construct a `GValueConstruct` with valid value for the “@protocol@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSocketProtocol :: (IsSocket o, MIO.MonadIO m) => Gio.Enums.SocketProtocol -> m (GValueConstruct o)
constructSocketProtocol :: forall o (m :: * -> *).
(IsSocket o, MonadIO m) =>
SocketProtocol -> m (GValueConstruct o)
constructSocketProtocol SocketProtocol
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> SocketProtocol -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"protocol" SocketProtocol
val

#if defined(ENABLE_OVERLOADING)
data SocketProtocolPropertyInfo
instance AttrInfo SocketProtocolPropertyInfo where
    type AttrAllowedOps SocketProtocolPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SocketProtocolPropertyInfo = IsSocket
    type AttrSetTypeConstraint SocketProtocolPropertyInfo = (~) Gio.Enums.SocketProtocol
    type AttrTransferTypeConstraint SocketProtocolPropertyInfo = (~) Gio.Enums.SocketProtocol
    type AttrTransferType SocketProtocolPropertyInfo = Gio.Enums.SocketProtocol
    type AttrGetType SocketProtocolPropertyInfo = Gio.Enums.SocketProtocol
    type AttrLabel SocketProtocolPropertyInfo = "protocol"
    type AttrOrigin SocketProtocolPropertyInfo = Socket
    attrGet = getSocketProtocol
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructSocketProtocol
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.protocol"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#g:attr:protocol"
        })
#endif

-- VVV Prop "remote-address"
   -- Type: TInterface (Name {namespace = "Gio", name = "SocketAddress"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

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

#if defined(ENABLE_OVERLOADING)
data SocketRemoteAddressPropertyInfo
instance AttrInfo SocketRemoteAddressPropertyInfo where
    type AttrAllowedOps SocketRemoteAddressPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SocketRemoteAddressPropertyInfo = IsSocket
    type AttrSetTypeConstraint SocketRemoteAddressPropertyInfo = (~) ()
    type AttrTransferTypeConstraint SocketRemoteAddressPropertyInfo = (~) ()
    type AttrTransferType SocketRemoteAddressPropertyInfo = ()
    type AttrGetType SocketRemoteAddressPropertyInfo = (Maybe Gio.SocketAddress.SocketAddress)
    type AttrLabel SocketRemoteAddressPropertyInfo = "remote-address"
    type AttrOrigin SocketRemoteAddressPropertyInfo = Socket
    attrGet = getSocketRemoteAddress
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.remoteAddress"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#g:attr:remoteAddress"
        })
#endif

-- VVV Prop "timeout"
   -- Type: TBasicType TUInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@timeout@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' socket #timeout
-- @
getSocketTimeout :: (MonadIO m, IsSocket o) => o -> m Word32
getSocketTimeout :: forall (m :: * -> *) o. (MonadIO m, IsSocket o) => o -> m Word32
getSocketTimeout o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"timeout"

-- | Set the value of the “@timeout@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' socket [ #timeout 'Data.GI.Base.Attributes.:=' value ]
-- @
setSocketTimeout :: (MonadIO m, IsSocket o) => o -> Word32 -> m ()
setSocketTimeout :: forall (m :: * -> *) o.
(MonadIO m, IsSocket o) =>
o -> Word32 -> m ()
setSocketTimeout o
obj Word32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"timeout" Word32
val

-- | Construct a `GValueConstruct` with valid value for the “@timeout@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSocketTimeout :: (IsSocket o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructSocketTimeout :: forall o (m :: * -> *).
(IsSocket o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructSocketTimeout Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"timeout" Word32
val

#if defined(ENABLE_OVERLOADING)
data SocketTimeoutPropertyInfo
instance AttrInfo SocketTimeoutPropertyInfo where
    type AttrAllowedOps SocketTimeoutPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SocketTimeoutPropertyInfo = IsSocket
    type AttrSetTypeConstraint SocketTimeoutPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint SocketTimeoutPropertyInfo = (~) Word32
    type AttrTransferType SocketTimeoutPropertyInfo = Word32
    type AttrGetType SocketTimeoutPropertyInfo = Word32
    type AttrLabel SocketTimeoutPropertyInfo = "timeout"
    type AttrOrigin SocketTimeoutPropertyInfo = Socket
    attrGet = getSocketTimeout
    attrSet = setSocketTimeout
    attrTransfer _ v = do
        return v
    attrConstruct = constructSocketTimeout
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.timeout"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#g:attr:timeout"
        })
#endif

-- VVV Prop "ttl"
   -- Type: TBasicType TUInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@ttl@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' socket #ttl
-- @
getSocketTtl :: (MonadIO m, IsSocket o) => o -> m Word32
getSocketTtl :: forall (m :: * -> *) o. (MonadIO m, IsSocket o) => o -> m Word32
getSocketTtl o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"ttl"

-- | Set the value of the “@ttl@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' socket [ #ttl 'Data.GI.Base.Attributes.:=' value ]
-- @
setSocketTtl :: (MonadIO m, IsSocket o) => o -> Word32 -> m ()
setSocketTtl :: forall (m :: * -> *) o.
(MonadIO m, IsSocket o) =>
o -> Word32 -> m ()
setSocketTtl o
obj Word32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"ttl" Word32
val

-- | Construct a `GValueConstruct` with valid value for the “@ttl@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSocketTtl :: (IsSocket o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructSocketTtl :: forall o (m :: * -> *).
(IsSocket o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructSocketTtl Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"ttl" Word32
val

#if defined(ENABLE_OVERLOADING)
data SocketTtlPropertyInfo
instance AttrInfo SocketTtlPropertyInfo where
    type AttrAllowedOps SocketTtlPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SocketTtlPropertyInfo = IsSocket
    type AttrSetTypeConstraint SocketTtlPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint SocketTtlPropertyInfo = (~) Word32
    type AttrTransferType SocketTtlPropertyInfo = Word32
    type AttrGetType SocketTtlPropertyInfo = Word32
    type AttrLabel SocketTtlPropertyInfo = "ttl"
    type AttrOrigin SocketTtlPropertyInfo = Socket
    attrGet = getSocketTtl
    attrSet = setSocketTtl
    attrTransfer _ v = do
        return v
    attrConstruct = constructSocketTtl
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.ttl"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#g:attr:ttl"
        })
#endif

-- VVV Prop "type"
   -- Type: TInterface (Name {namespace = "Gio", name = "SocketType"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@type@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' socket #type
-- @
getSocketType :: (MonadIO m, IsSocket o) => o -> m Gio.Enums.SocketType
getSocketType :: forall (m :: * -> *) o.
(MonadIO m, IsSocket o) =>
o -> m SocketType
getSocketType o
obj = IO SocketType -> m SocketType
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO SocketType -> m SocketType) -> IO SocketType -> m SocketType
forall a b. (a -> b) -> a -> b
$ o -> String -> IO SocketType
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"type"

-- | Construct a `GValueConstruct` with valid value for the “@type@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSocketType :: (IsSocket o, MIO.MonadIO m) => Gio.Enums.SocketType -> m (GValueConstruct o)
constructSocketType :: forall o (m :: * -> *).
(IsSocket o, MonadIO m) =>
SocketType -> m (GValueConstruct o)
constructSocketType SocketType
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> SocketType -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"type" SocketType
val

#if defined(ENABLE_OVERLOADING)
data SocketTypePropertyInfo
instance AttrInfo SocketTypePropertyInfo where
    type AttrAllowedOps SocketTypePropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SocketTypePropertyInfo = IsSocket
    type AttrSetTypeConstraint SocketTypePropertyInfo = (~) Gio.Enums.SocketType
    type AttrTransferTypeConstraint SocketTypePropertyInfo = (~) Gio.Enums.SocketType
    type AttrTransferType SocketTypePropertyInfo = Gio.Enums.SocketType
    type AttrGetType SocketTypePropertyInfo = Gio.Enums.SocketType
    type AttrLabel SocketTypePropertyInfo = "type"
    type AttrOrigin SocketTypePropertyInfo = Socket
    attrGet = getSocketType
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructSocketType
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.type"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#g:attr:type"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Socket
type instance O.AttributeList Socket = SocketAttributeList
type SocketAttributeList = ('[ '("blocking", SocketBlockingPropertyInfo), '("broadcast", SocketBroadcastPropertyInfo), '("family", SocketFamilyPropertyInfo), '("fd", SocketFdPropertyInfo), '("keepalive", SocketKeepalivePropertyInfo), '("listenBacklog", SocketListenBacklogPropertyInfo), '("localAddress", SocketLocalAddressPropertyInfo), '("multicastLoopback", SocketMulticastLoopbackPropertyInfo), '("multicastTtl", SocketMulticastTtlPropertyInfo), '("protocol", SocketProtocolPropertyInfo), '("remoteAddress", SocketRemoteAddressPropertyInfo), '("timeout", SocketTimeoutPropertyInfo), '("ttl", SocketTtlPropertyInfo), '("type", SocketTypePropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
socketBlocking :: AttrLabelProxy "blocking"
socketBlocking = AttrLabelProxy

socketBroadcast :: AttrLabelProxy "broadcast"
socketBroadcast = AttrLabelProxy

socketFamily :: AttrLabelProxy "family"
socketFamily = AttrLabelProxy

socketFd :: AttrLabelProxy "fd"
socketFd = AttrLabelProxy

socketKeepalive :: AttrLabelProxy "keepalive"
socketKeepalive = AttrLabelProxy

socketListenBacklog :: AttrLabelProxy "listenBacklog"
socketListenBacklog = AttrLabelProxy

socketLocalAddress :: AttrLabelProxy "localAddress"
socketLocalAddress = AttrLabelProxy

socketMulticastLoopback :: AttrLabelProxy "multicastLoopback"
socketMulticastLoopback = AttrLabelProxy

socketMulticastTtl :: AttrLabelProxy "multicastTtl"
socketMulticastTtl = AttrLabelProxy

socketProtocol :: AttrLabelProxy "protocol"
socketProtocol = AttrLabelProxy

socketRemoteAddress :: AttrLabelProxy "remoteAddress"
socketRemoteAddress = AttrLabelProxy

socketTimeout :: AttrLabelProxy "timeout"
socketTimeout = AttrLabelProxy

socketTtl :: AttrLabelProxy "ttl"
socketTtl = AttrLabelProxy

socketType :: AttrLabelProxy "type"
socketType = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Socket = SocketSignalList
type SocketSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method Socket::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "family"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SocketFamily" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the socket family to use, e.g. %G_SOCKET_FAMILY_IPV4."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "type"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SocketType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the socket type to use."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "protocol"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SocketProtocol" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the id of the protocol to use, or 0 for default."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "Socket" })
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_new" g_socket_new :: 
    CUInt ->                                -- family : TInterface (Name {namespace = "Gio", name = "SocketFamily"})
    CUInt ->                                -- type : TInterface (Name {namespace = "Gio", name = "SocketType"})
    CInt ->                                 -- protocol : TInterface (Name {namespace = "Gio", name = "SocketProtocol"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Socket)

-- | Creates a new t'GI.Gio.Objects.Socket.Socket' with the defined family, type and protocol.
-- If /@protocol@/ is 0 ('GI.Gio.Enums.SocketProtocolDefault') the default protocol type
-- for the family and type is used.
-- 
-- The /@protocol@/ is a family and type specific int that specifies what
-- kind of protocol to use. t'GI.Gio.Enums.SocketProtocol' lists several common ones.
-- Many families only support one protocol, and use 0 for this, others
-- support several and using 0 means to use the default protocol for
-- the family and type.
-- 
-- The protocol id is passed directly to the operating
-- system, so you can use protocols not listed in t'GI.Gio.Enums.SocketProtocol' if you
-- know the protocol number used for it.
-- 
-- /Since: 2.22/
socketNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Gio.Enums.SocketFamily
    -- ^ /@family@/: the socket family to use, e.g. 'GI.Gio.Enums.SocketFamilyIpv4'.
    -> Gio.Enums.SocketType
    -- ^ /@type@/: the socket type to use.
    -> Gio.Enums.SocketProtocol
    -- ^ /@protocol@/: the id of the protocol to use, or 0 for default.
    -> m Socket
    -- ^ __Returns:__ a t'GI.Gio.Objects.Socket.Socket' or 'P.Nothing' on error.
    --     Free the returned object with 'GI.GObject.Objects.Object.objectUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
socketNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SocketFamily -> SocketType -> SocketProtocol -> m Socket
socketNew SocketFamily
family SocketType
type_ SocketProtocol
protocol = IO Socket -> m Socket
forall a. IO a -> m a
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
    let family' :: CUInt
family' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (SocketFamily -> Int) -> SocketFamily -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SocketFamily -> Int
forall a. Enum a => a -> Int
fromEnum) SocketFamily
family
    let type_' :: CUInt
type_' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (SocketType -> Int) -> SocketType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SocketType -> Int
forall a. Enum a => a -> Int
fromEnum) SocketType
type_
    let protocol' :: CInt
protocol' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (SocketProtocol -> Int) -> SocketProtocol -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SocketProtocol -> Int
forall a. Enum a => a -> Int
fromEnum) SocketProtocol
protocol
    IO Socket -> IO () -> IO Socket
forall a b. IO a -> IO b -> IO a
onException (do
        result <- (Ptr (Ptr GError) -> IO (Ptr Socket)) -> IO (Ptr Socket)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Socket)) -> IO (Ptr Socket))
-> (Ptr (Ptr GError) -> IO (Ptr Socket)) -> IO (Ptr Socket)
forall a b. (a -> b) -> a -> b
$ CUInt -> CUInt -> CInt -> Ptr (Ptr GError) -> IO (Ptr Socket)
g_socket_new CUInt
family' CUInt
type_' CInt
protocol'
        checkUnexpectedReturnNULL "socketNew" result
        result' <- (wrapObject Socket) result
        return result'
     ) (do
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method Socket::new_from_fd
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "fd"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a native socket file descriptor."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "Socket" })
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_new_from_fd" g_socket_new_from_fd :: 
    Int32 ->                                -- fd : TBasicType TInt
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Socket)

-- | Creates a new t'GI.Gio.Objects.Socket.Socket' from a native file descriptor
-- or winsock SOCKET handle.
-- 
-- This reads all the settings from the file descriptor so that
-- all properties should work. Note that the file descriptor
-- will be set to non-blocking mode, independent on the blocking
-- mode of the t'GI.Gio.Objects.Socket.Socket'.
-- 
-- On success, the returned t'GI.Gio.Objects.Socket.Socket' takes ownership of /@fd@/. On failure, the
-- caller must close /@fd@/ themselves.
-- 
-- Since GLib 2.46, it is no longer a fatal error to call this on a non-socket
-- descriptor.  Instead, a GError will be set with code 'GI.Gio.Enums.IOErrorEnumFailed'
-- 
-- /Since: 2.22/
socketNewFromFd ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Int32
    -- ^ /@fd@/: a native socket file descriptor.
    -> m Socket
    -- ^ __Returns:__ a t'GI.Gio.Objects.Socket.Socket' or 'P.Nothing' on error.
    --     Free the returned object with 'GI.GObject.Objects.Object.objectUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
socketNewFromFd :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Int32 -> m Socket
socketNewFromFd Int32
fd = IO Socket -> m Socket
forall a. IO a -> m a
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
    IO Socket -> IO () -> IO Socket
forall a b. IO a -> IO b -> IO a
onException (do
        result <- (Ptr (Ptr GError) -> IO (Ptr Socket)) -> IO (Ptr Socket)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Socket)) -> IO (Ptr Socket))
-> (Ptr (Ptr GError) -> IO (Ptr Socket)) -> IO (Ptr Socket)
forall a b. (a -> b) -> a -> b
$ Int32 -> Ptr (Ptr GError) -> IO (Ptr Socket)
g_socket_new_from_fd Int32
fd
        checkUnexpectedReturnNULL "socketNewFromFd" result
        result' <- (wrapObject Socket) result
        return result'
     ) (do
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method Socket::accept
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a %GCancellable or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "Socket" })
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_accept" g_socket_accept :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Socket)

-- | Accept incoming connections on a connection-based socket. This removes
-- the first outstanding connection request from the listening socket and
-- creates a t'GI.Gio.Objects.Socket.Socket' object for it.
-- 
-- The /@socket@/ must be bound to a local address with 'GI.Gio.Objects.Socket.socketBind' and
-- must be listening for incoming connections ('GI.Gio.Objects.Socket.socketListen').
-- 
-- If there are no outstanding connections then the operation will block
-- or return 'GI.Gio.Enums.IOErrorEnumWouldBlock' if non-blocking I\/O is enabled.
-- To be notified of an incoming connection, wait for the 'GI.GObject.Flags.IOConditionIn' condition.
-- 
-- /Since: 2.22/
socketAccept ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> Maybe (b)
    -- ^ /@cancellable@/: a @/GCancellable/@ or 'P.Nothing'
    -> m Socket
    -- ^ __Returns:__ a new t'GI.Gio.Objects.Socket.Socket', or 'P.Nothing' on error.
    --     Free the returned object with 'GI.GObject.Objects.Object.objectUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
socketAccept :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSocket a, IsCancellable b) =>
a -> Maybe b -> m Socket
socketAccept a
socket Maybe b
cancellable = IO Socket -> m Socket
forall a. IO a -> m a
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
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    maybeCancellable <- case cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just b
jCancellable -> do
            jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_socket_accept socket' maybeCancellable
        checkUnexpectedReturnNULL "socketAccept" result
        result' <- (wrapObject Socket) result
        touchManagedPtr socket
        whenJust cancellable touchManagedPtr
        return result'
     ) (do
        return ()
     )

#if defined(ENABLE_OVERLOADING)
data SocketAcceptMethodInfo
instance (signature ~ (Maybe (b) -> m Socket), MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod SocketAcceptMethodInfo a signature where
    overloadedMethod = socketAccept

instance O.OverloadedMethodInfo SocketAcceptMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketAccept",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketAccept"
        })


#endif

-- method Socket::bind
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "address"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SocketAddress" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GSocketAddress specifying the local address."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "allow_reuse"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether to allow reusing this address"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_bind" g_socket_bind :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Ptr Gio.SocketAddress.SocketAddress ->  -- address : TInterface (Name {namespace = "Gio", name = "SocketAddress"})
    CInt ->                                 -- allow_reuse : TBasicType TBoolean
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | When a socket is created it is attached to an address family, but it
-- doesn\'t have an address in this family. 'GI.Gio.Objects.Socket.socketBind' assigns the
-- address (sometimes called name) of the socket.
-- 
-- It is generally required to bind to a local address before you can
-- receive connections. (See 'GI.Gio.Objects.Socket.socketListen' and 'GI.Gio.Objects.Socket.socketAccept' ).
-- In certain situations, you may also want to bind a socket that will be
-- used to initiate connections, though this is not normally required.
-- 
-- If /@socket@/ is a TCP socket, then /@allowReuse@/ controls the setting
-- of the @SO_REUSEADDR@ socket option; normally it should be 'P.True' for
-- server sockets (sockets that you will eventually call
-- 'GI.Gio.Objects.Socket.socketAccept' on), and 'P.False' for client sockets. (Failing to
-- set this flag on a server socket may cause 'GI.Gio.Objects.Socket.socketBind' to return
-- 'GI.Gio.Enums.IOErrorEnumAddressInUse' if the server program is stopped and then
-- immediately restarted.)
-- 
-- If /@socket@/ is a UDP socket, then /@allowReuse@/ determines whether or
-- not other UDP sockets can be bound to the same address at the same
-- time. In particular, you can have several UDP sockets bound to the
-- same address, and they will all receive all of the multicast and
-- broadcast packets sent to that address. (The behavior of unicast
-- UDP packets to an address with multiple listeners is not defined.)
-- 
-- /Since: 2.22/
socketBind ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.SocketAddress.IsSocketAddress b) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> b
    -- ^ /@address@/: a t'GI.Gio.Objects.SocketAddress.SocketAddress' specifying the local address.
    -> Bool
    -- ^ /@allowReuse@/: whether to allow reusing this address
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
socketBind :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSocket a, IsSocketAddress b) =>
a -> b -> Bool -> m ()
socketBind a
socket b
address Bool
allowReuse = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    address' <- unsafeManagedPtrCastPtr address
    let allowReuse' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
allowReuse
    onException (do
        _ <- propagateGError $ g_socket_bind socket' address' allowReuse'
        touchManagedPtr socket
        touchManagedPtr address
        return ()
     ) (do
        return ()
     )

#if defined(ENABLE_OVERLOADING)
data SocketBindMethodInfo
instance (signature ~ (b -> Bool -> m ()), MonadIO m, IsSocket a, Gio.SocketAddress.IsSocketAddress b) => O.OverloadedMethod SocketBindMethodInfo a signature where
    overloadedMethod = socketBind

instance O.OverloadedMethodInfo SocketBindMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketBind",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketBind"
        })


#endif

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

foreign import ccall "g_socket_check_connect_result" g_socket_check_connect_result :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Checks and resets the pending connect error for the socket.
-- This is used to check for errors when 'GI.Gio.Objects.Socket.socketConnect' is
-- used in non-blocking mode.
-- 
-- /Since: 2.22/
socketCheckConnectResult ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
socketCheckConnectResult :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> m ()
socketCheckConnectResult a
socket = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    onException (do
        _ <- propagateGError $ g_socket_check_connect_result socket'
        touchManagedPtr socket
        return ()
     ) (do
        return ()
     )

#if defined(ENABLE_OVERLOADING)
data SocketCheckConnectResultMethodInfo
instance (signature ~ (m ()), MonadIO m, IsSocket a) => O.OverloadedMethod SocketCheckConnectResultMethodInfo a signature where
    overloadedMethod = socketCheckConnectResult

instance O.OverloadedMethodInfo SocketCheckConnectResultMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketCheckConnectResult",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketCheckConnectResult"
        })


#endif

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

foreign import ccall "g_socket_close" g_socket_close :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Closes the socket, shutting down any active connection.
-- 
-- Closing a socket does not wait for all outstanding I\/O operations
-- to finish, so the caller should not rely on them to be guaranteed
-- to complete even if the close returns with no error.
-- 
-- Once the socket is closed, all other operations will return
-- 'GI.Gio.Enums.IOErrorEnumClosed'. Closing a socket multiple times will not
-- return an error.
-- 
-- Sockets will be automatically closed when the last reference
-- is dropped, but you might want to call this function to make sure
-- resources are released as early as possible.
-- 
-- Beware that due to the way that TCP works, it is possible for
-- recently-sent data to be lost if either you close a socket while the
-- 'GI.GObject.Flags.IOConditionIn' condition is set, or else if the remote connection tries to
-- send something to you after you close the socket but before it has
-- finished reading all of the data you sent. There is no easy generic
-- way to avoid this problem; the easiest fix is to design the network
-- protocol such that the client will never send data \"out of turn\".
-- Another solution is for the server to half-close the connection by
-- calling 'GI.Gio.Objects.Socket.socketShutdown' with only the /@shutdownWrite@/ flag set,
-- and then wait for the client to notice this and close its side of the
-- connection, after which the server can safely call 'GI.Gio.Objects.Socket.socketClose'.
-- (This is what t'GI.Gio.Objects.TcpConnection.TcpConnection' does if you call
-- 'GI.Gio.Objects.TcpConnection.tcpConnectionSetGracefulDisconnect'. But of course, this
-- only works if the client will close its connection after the server
-- does.)
-- 
-- /Since: 2.22/
socketClose ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
socketClose :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> m ()
socketClose a
socket = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    onException (do
        _ <- propagateGError $ g_socket_close socket'
        touchManagedPtr socket
        return ()
     ) (do
        return ()
     )

#if defined(ENABLE_OVERLOADING)
data SocketCloseMethodInfo
instance (signature ~ (m ()), MonadIO m, IsSocket a) => O.OverloadedMethod SocketCloseMethodInfo a signature where
    overloadedMethod = socketClose

instance O.OverloadedMethodInfo SocketCloseMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketClose",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketClose"
        })


#endif

-- method Socket::condition_check
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "condition"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "IOCondition" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GIOCondition mask to check"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GLib" , name = "IOCondition" })
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_condition_check" g_socket_condition_check :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    CUInt ->                                -- condition : TInterface (Name {namespace = "GLib", name = "IOCondition"})
    IO CUInt

-- | Checks on the readiness of /@socket@/ to perform operations.
-- The operations specified in /@condition@/ are checked for and masked
-- against the currently-satisfied conditions on /@socket@/. The result
-- is returned.
-- 
-- Note that on Windows, it is possible for an operation to return
-- 'GI.Gio.Enums.IOErrorEnumWouldBlock' even immediately after
-- 'GI.Gio.Objects.Socket.socketConditionCheck' has claimed that the socket is ready for
-- writing. Rather than calling 'GI.Gio.Objects.Socket.socketConditionCheck' and then
-- writing to the socket if it succeeds, it is generally better to
-- simply try writing to the socket right away, and try again later if
-- the initial attempt returns 'GI.Gio.Enums.IOErrorEnumWouldBlock'.
-- 
-- It is meaningless to specify 'GI.GObject.Flags.IOConditionErr' or 'GI.GObject.Flags.IOConditionHup' in condition;
-- these conditions will always be set in the output if they are true.
-- 
-- This call never blocks.
-- 
-- /Since: 2.22/
socketConditionCheck ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'
    -> [GLib.Flags.IOCondition]
    -- ^ /@condition@/: a t'GI.GObject.Flags.IOCondition' mask to check
    -> m [GLib.Flags.IOCondition]
    -- ^ __Returns:__ the /@gIOCondition@/ mask of the current state
socketConditionCheck :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> [IOCondition] -> m [IOCondition]
socketConditionCheck a
socket [IOCondition]
condition = IO [IOCondition] -> m [IOCondition]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [IOCondition] -> m [IOCondition])
-> IO [IOCondition] -> m [IOCondition]
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    let condition' = [IOCondition] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [IOCondition]
condition
    result <- g_socket_condition_check socket' condition'
    let result' = CUInt -> [IOCondition]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    touchManagedPtr socket
    return result'

#if defined(ENABLE_OVERLOADING)
data SocketConditionCheckMethodInfo
instance (signature ~ ([GLib.Flags.IOCondition] -> m [GLib.Flags.IOCondition]), MonadIO m, IsSocket a) => O.OverloadedMethod SocketConditionCheckMethodInfo a signature where
    overloadedMethod = socketConditionCheck

instance O.OverloadedMethodInfo SocketConditionCheckMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketConditionCheck",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketConditionCheck"
        })


#endif

-- method Socket::condition_timed_wait
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "condition"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "IOCondition" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GIOCondition mask to wait for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "timeout_us"
--           , argType = TBasicType TInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the maximum time (in microseconds) to wait, or -1"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GCancellable, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_condition_timed_wait" g_socket_condition_timed_wait :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    CUInt ->                                -- condition : TInterface (Name {namespace = "GLib", name = "IOCondition"})
    Int64 ->                                -- timeout_us : TBasicType TInt64
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Waits for up to /@timeoutUs@/ microseconds for /@condition@/ to become true
-- on /@socket@/. If the condition is met, 'P.True' is returned.
-- 
-- If /@cancellable@/ is cancelled before the condition is met, or if
-- /@timeoutUs@/ (or the socket\'s [Socket:timeout]("GI.Gio.Objects.Socket#g:attr:timeout")) is reached before the
-- condition is met, then 'P.False' is returned and /@error@/, if non-'P.Nothing',
-- is set to the appropriate value ('GI.Gio.Enums.IOErrorEnumCancelled' or
-- 'GI.Gio.Enums.IOErrorEnumTimedOut').
-- 
-- If you don\'t want a timeout, use 'GI.Gio.Objects.Socket.socketConditionWait'.
-- (Alternatively, you can pass -1 for /@timeoutUs@/.)
-- 
-- Note that although /@timeoutUs@/ is in microseconds for consistency with
-- other GLib APIs, this function actually only has millisecond
-- resolution, and the behavior is undefined if /@timeoutUs@/ is not an
-- exact number of milliseconds.
-- 
-- /Since: 2.32/
socketConditionTimedWait ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'
    -> [GLib.Flags.IOCondition]
    -- ^ /@condition@/: a t'GI.GObject.Flags.IOCondition' mask to wait for
    -> Int64
    -- ^ /@timeoutUs@/: the maximum time (in microseconds) to wait, or -1
    -> Maybe (b)
    -- ^ /@cancellable@/: a t'GI.Gio.Objects.Cancellable.Cancellable', or 'P.Nothing'
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
socketConditionTimedWait :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSocket a, IsCancellable b) =>
a -> [IOCondition] -> Int64 -> Maybe b -> m ()
socketConditionTimedWait a
socket [IOCondition]
condition Int64
timeoutUs Maybe b
cancellable = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    let condition' = [IOCondition] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [IOCondition]
condition
    maybeCancellable <- case cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just b
jCancellable -> do
            jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            return jCancellable'
    onException (do
        _ <- propagateGError $ g_socket_condition_timed_wait socket' condition' timeoutUs maybeCancellable
        touchManagedPtr socket
        whenJust cancellable touchManagedPtr
        return ()
     ) (do
        return ()
     )

#if defined(ENABLE_OVERLOADING)
data SocketConditionTimedWaitMethodInfo
instance (signature ~ ([GLib.Flags.IOCondition] -> Int64 -> Maybe (b) -> m ()), MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod SocketConditionTimedWaitMethodInfo a signature where
    overloadedMethod = socketConditionTimedWait

instance O.OverloadedMethodInfo SocketConditionTimedWaitMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketConditionTimedWait",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketConditionTimedWait"
        })


#endif

-- method Socket::condition_wait
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "condition"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "IOCondition" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GIOCondition mask to wait for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GCancellable, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_condition_wait" g_socket_condition_wait :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    CUInt ->                                -- condition : TInterface (Name {namespace = "GLib", name = "IOCondition"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Waits for /@condition@/ to become true on /@socket@/. When the condition
-- is met, 'P.True' is returned.
-- 
-- If /@cancellable@/ is cancelled before the condition is met, or if the
-- socket has a timeout set and it is reached before the condition is
-- met, then 'P.False' is returned and /@error@/, if non-'P.Nothing', is set to
-- the appropriate value ('GI.Gio.Enums.IOErrorEnumCancelled' or
-- 'GI.Gio.Enums.IOErrorEnumTimedOut').
-- 
-- See also 'GI.Gio.Objects.Socket.socketConditionTimedWait'.
-- 
-- /Since: 2.22/
socketConditionWait ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'
    -> [GLib.Flags.IOCondition]
    -- ^ /@condition@/: a t'GI.GObject.Flags.IOCondition' mask to wait for
    -> Maybe (b)
    -- ^ /@cancellable@/: a t'GI.Gio.Objects.Cancellable.Cancellable', or 'P.Nothing'
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
socketConditionWait :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSocket a, IsCancellable b) =>
a -> [IOCondition] -> Maybe b -> m ()
socketConditionWait a
socket [IOCondition]
condition Maybe b
cancellable = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    let condition' = [IOCondition] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [IOCondition]
condition
    maybeCancellable <- case cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just b
jCancellable -> do
            jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            return jCancellable'
    onException (do
        _ <- propagateGError $ g_socket_condition_wait socket' condition' maybeCancellable
        touchManagedPtr socket
        whenJust cancellable touchManagedPtr
        return ()
     ) (do
        return ()
     )

#if defined(ENABLE_OVERLOADING)
data SocketConditionWaitMethodInfo
instance (signature ~ ([GLib.Flags.IOCondition] -> Maybe (b) -> m ()), MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod SocketConditionWaitMethodInfo a signature where
    overloadedMethod = socketConditionWait

instance O.OverloadedMethodInfo SocketConditionWaitMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketConditionWait",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketConditionWait"
        })


#endif

-- method Socket::connect
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "address"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SocketAddress" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GSocketAddress specifying the remote address."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a %GCancellable or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_connect" g_socket_connect :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Ptr Gio.SocketAddress.SocketAddress ->  -- address : TInterface (Name {namespace = "Gio", name = "SocketAddress"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Connect the socket to the specified remote address.
-- 
-- For connection oriented socket this generally means we attempt to make
-- a connection to the /@address@/. For a connection-less socket it sets
-- the default address for 'GI.Gio.Objects.Socket.socketSend' and discards all incoming datagrams
-- from other sources.
-- 
-- Generally connection oriented sockets can only connect once, but
-- connection-less sockets can connect multiple times to change the
-- default address.
-- 
-- If the connect call needs to do network I\/O it will block, unless
-- non-blocking I\/O is enabled. Then 'GI.Gio.Enums.IOErrorEnumPending' is returned
-- and the user can be notified of the connection finishing by waiting
-- for the G_IO_OUT condition. The result of the connection must then be
-- checked with 'GI.Gio.Objects.Socket.socketCheckConnectResult'.
-- 
-- /Since: 2.22/
socketConnect ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.SocketAddress.IsSocketAddress b, Gio.Cancellable.IsCancellable c) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> b
    -- ^ /@address@/: a t'GI.Gio.Objects.SocketAddress.SocketAddress' specifying the remote address.
    -> Maybe (c)
    -- ^ /@cancellable@/: a @/GCancellable/@ or 'P.Nothing'
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
socketConnect :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsSocket a, IsSocketAddress b,
 IsCancellable c) =>
a -> b -> Maybe c -> m ()
socketConnect a
socket b
address Maybe c
cancellable = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    address' <- unsafeManagedPtrCastPtr address
    maybeCancellable <- case cancellable of
        Maybe c
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just c
jCancellable -> do
            jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
            return jCancellable'
    onException (do
        _ <- propagateGError $ g_socket_connect socket' address' maybeCancellable
        touchManagedPtr socket
        touchManagedPtr address
        whenJust cancellable touchManagedPtr
        return ()
     ) (do
        return ()
     )

#if defined(ENABLE_OVERLOADING)
data SocketConnectMethodInfo
instance (signature ~ (b -> Maybe (c) -> m ()), MonadIO m, IsSocket a, Gio.SocketAddress.IsSocketAddress b, Gio.Cancellable.IsCancellable c) => O.OverloadedMethod SocketConnectMethodInfo a signature where
    overloadedMethod = socketConnect

instance O.OverloadedMethodInfo SocketConnectMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketConnect",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketConnect"
        })


#endif

-- method Socket::connection_factory_create_connection
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "SocketConnection" })
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_connection_factory_create_connection" g_socket_connection_factory_create_connection :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    IO (Ptr Gio.SocketConnection.SocketConnection)

-- | Creates a t'GI.Gio.Objects.SocketConnection.SocketConnection' subclass of the right type for
-- /@socket@/.
-- 
-- /Since: 2.22/
socketConnectionFactoryCreateConnection ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'
    -> m Gio.SocketConnection.SocketConnection
    -- ^ __Returns:__ a t'GI.Gio.Objects.SocketConnection.SocketConnection'
socketConnectionFactoryCreateConnection :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> m SocketConnection
socketConnectionFactoryCreateConnection a
socket = IO SocketConnection -> m SocketConnection
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SocketConnection -> m SocketConnection)
-> IO SocketConnection -> m SocketConnection
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    result <- g_socket_connection_factory_create_connection socket'
    checkUnexpectedReturnNULL "socketConnectionFactoryCreateConnection" result
    result' <- (wrapObject Gio.SocketConnection.SocketConnection) result
    touchManagedPtr socket
    return result'

#if defined(ENABLE_OVERLOADING)
data SocketConnectionFactoryCreateConnectionMethodInfo
instance (signature ~ (m Gio.SocketConnection.SocketConnection), MonadIO m, IsSocket a) => O.OverloadedMethod SocketConnectionFactoryCreateConnectionMethodInfo a signature where
    overloadedMethod = socketConnectionFactoryCreateConnection

instance O.OverloadedMethodInfo SocketConnectionFactoryCreateConnectionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketConnectionFactoryCreateConnection",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketConnectionFactoryCreateConnection"
        })


#endif

-- method Socket::get_available_bytes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TSSize)
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_get_available_bytes" g_socket_get_available_bytes :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    IO DI.Int64

-- | Get the amount of data pending in the OS input buffer, without blocking.
-- 
-- If /@socket@/ is a UDP or SCTP socket, this will return the size of
-- just the next packet, even if additional packets are buffered after
-- that one.
-- 
-- Note that on Windows, this function is rather inefficient in the
-- UDP case, and so if you know any plausible upper bound on the size
-- of the incoming packet, it is better to just do a
-- 'GI.Gio.Objects.Socket.socketReceive' with a buffer of that size, rather than calling
-- 'GI.Gio.Objects.Socket.socketGetAvailableBytes' first and then doing a receive of
-- exactly the right size.
-- 
-- /Since: 2.32/
socketGetAvailableBytes ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'
    -> m DI.Int64
    -- ^ __Returns:__ the number of bytes that can be read from the socket
    -- without blocking or truncating, or -1 on error.
socketGetAvailableBytes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> m Int64
socketGetAvailableBytes a
socket = IO Int64 -> m Int64
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int64 -> m Int64) -> IO Int64 -> m Int64
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    result <- g_socket_get_available_bytes socket'
    touchManagedPtr socket
    return result

#if defined(ENABLE_OVERLOADING)
data SocketGetAvailableBytesMethodInfo
instance (signature ~ (m DI.Int64), MonadIO m, IsSocket a) => O.OverloadedMethod SocketGetAvailableBytesMethodInfo a signature where
    overloadedMethod = socketGetAvailableBytes

instance O.OverloadedMethodInfo SocketGetAvailableBytesMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketGetAvailableBytes",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketGetAvailableBytes"
        })


#endif

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

foreign import ccall "g_socket_get_blocking" g_socket_get_blocking :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    IO CInt

-- | Gets the blocking mode of the socket. For details on blocking I\/O,
-- see 'GI.Gio.Objects.Socket.socketSetBlocking'.
-- 
-- /Since: 2.22/
socketGetBlocking ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if blocking I\/O is used, 'P.False' otherwise.
socketGetBlocking :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> m Bool
socketGetBlocking a
socket = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    result <- g_socket_get_blocking socket'
    let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    touchManagedPtr socket
    return result'

#if defined(ENABLE_OVERLOADING)
data SocketGetBlockingMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSocket a) => O.OverloadedMethod SocketGetBlockingMethodInfo a signature where
    overloadedMethod = socketGetBlocking

instance O.OverloadedMethodInfo SocketGetBlockingMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketGetBlocking",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketGetBlocking"
        })


#endif

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

foreign import ccall "g_socket_get_broadcast" g_socket_get_broadcast :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    IO CInt

-- | Gets the broadcast setting on /@socket@/; if 'P.True',
-- it is possible to send packets to broadcast
-- addresses.
-- 
-- /Since: 2.32/
socketGetBroadcast ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> m Bool
    -- ^ __Returns:__ the broadcast setting on /@socket@/
socketGetBroadcast :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> m Bool
socketGetBroadcast a
socket = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    result <- g_socket_get_broadcast socket'
    let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    touchManagedPtr socket
    return result'

#if defined(ENABLE_OVERLOADING)
data SocketGetBroadcastMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSocket a) => O.OverloadedMethod SocketGetBroadcastMethodInfo a signature where
    overloadedMethod = socketGetBroadcast

instance O.OverloadedMethodInfo SocketGetBroadcastMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketGetBroadcast",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketGetBroadcast"
        })


#endif

-- method Socket::get_credentials
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "Credentials" })
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_get_credentials" g_socket_get_credentials :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Gio.Credentials.Credentials)

-- | Returns the credentials of the foreign process connected to this
-- socket, if any (e.g. it is only supported for 'GI.Gio.Enums.SocketFamilyUnix'
-- sockets).
-- 
-- If this operation isn\'t supported on the OS, the method fails with
-- the 'GI.Gio.Enums.IOErrorEnumNotSupported' error. On Linux this is implemented
-- by reading the @/SO_PEERCRED/@ option on the underlying socket.
-- 
-- This method can be expected to be available on the following platforms:
-- 
-- * Linux since GLib 2.26
-- * OpenBSD since GLib 2.30
-- * Solaris, Illumos and OpenSolaris since GLib 2.40
-- * NetBSD since GLib 2.42
-- * macOS, tvOS, iOS since GLib 2.66
-- 
-- 
-- Other ways to obtain credentials from a foreign peer includes the
-- t'GI.Gio.Objects.UnixCredentialsMessage.UnixCredentialsMessage' type and
-- 'GI.Gio.Objects.UnixConnection.unixConnectionSendCredentials' \/
-- 'GI.Gio.Objects.UnixConnection.unixConnectionReceiveCredentials' functions.
-- 
-- /Since: 2.26/
socketGetCredentials ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> m Gio.Credentials.Credentials
    -- ^ __Returns:__ 'P.Nothing' if /@error@/ is set, otherwise a t'GI.Gio.Objects.Credentials.Credentials' object
    -- that must be freed with 'GI.GObject.Objects.Object.objectUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
socketGetCredentials :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> m Credentials
socketGetCredentials a
socket = IO Credentials -> m Credentials
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Credentials -> m Credentials)
-> IO Credentials -> m Credentials
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    onException (do
        result <- propagateGError $ g_socket_get_credentials socket'
        checkUnexpectedReturnNULL "socketGetCredentials" result
        result' <- (wrapObject Gio.Credentials.Credentials) result
        touchManagedPtr socket
        return result'
     ) (do
        return ()
     )

#if defined(ENABLE_OVERLOADING)
data SocketGetCredentialsMethodInfo
instance (signature ~ (m Gio.Credentials.Credentials), MonadIO m, IsSocket a) => O.OverloadedMethod SocketGetCredentialsMethodInfo a signature where
    overloadedMethod = socketGetCredentials

instance O.OverloadedMethodInfo SocketGetCredentialsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketGetCredentials",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketGetCredentials"
        })


#endif

-- method Socket::get_family
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "SocketFamily" })
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_get_family" g_socket_get_family :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    IO CUInt

-- | Gets the socket family of the socket.
-- 
-- /Since: 2.22/
socketGetFamily ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> m Gio.Enums.SocketFamily
    -- ^ __Returns:__ a t'GI.Gio.Enums.SocketFamily'
socketGetFamily :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> m SocketFamily
socketGetFamily a
socket = IO SocketFamily -> m SocketFamily
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SocketFamily -> m SocketFamily)
-> IO SocketFamily -> m SocketFamily
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    result <- g_socket_get_family socket'
    let result' = (Int -> SocketFamily
forall a. Enum a => Int -> a
toEnum (Int -> SocketFamily) -> (CUInt -> Int) -> CUInt -> SocketFamily
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    touchManagedPtr socket
    return result'

#if defined(ENABLE_OVERLOADING)
data SocketGetFamilyMethodInfo
instance (signature ~ (m Gio.Enums.SocketFamily), MonadIO m, IsSocket a) => O.OverloadedMethod SocketGetFamilyMethodInfo a signature where
    overloadedMethod = socketGetFamily

instance O.OverloadedMethodInfo SocketGetFamilyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketGetFamily",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketGetFamily"
        })


#endif

-- method Socket::get_fd
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_get_fd" g_socket_get_fd :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    IO Int32

-- | Returns the underlying OS socket object. On unix this
-- is a socket file descriptor, and on Windows this is
-- a Winsock2 SOCKET handle. This may be useful for
-- doing platform specific or otherwise unusual operations
-- on the socket.
-- 
-- /Since: 2.22/
socketGetFd ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> m Int32
    -- ^ __Returns:__ the file descriptor of the socket.
socketGetFd :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> m Int32
socketGetFd a
socket = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    result <- g_socket_get_fd socket'
    touchManagedPtr socket
    return result

#if defined(ENABLE_OVERLOADING)
data SocketGetFdMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsSocket a) => O.OverloadedMethod SocketGetFdMethodInfo a signature where
    overloadedMethod = socketGetFd

instance O.OverloadedMethodInfo SocketGetFdMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketGetFd",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketGetFd"
        })


#endif

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

foreign import ccall "g_socket_get_keepalive" g_socket_get_keepalive :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    IO CInt

-- | Gets the keepalive mode of the socket. For details on this,
-- see 'GI.Gio.Objects.Socket.socketSetKeepalive'.
-- 
-- /Since: 2.22/
socketGetKeepalive ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if keepalive is active, 'P.False' otherwise.
socketGetKeepalive :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> m Bool
socketGetKeepalive a
socket = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    result <- g_socket_get_keepalive socket'
    let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    touchManagedPtr socket
    return result'

#if defined(ENABLE_OVERLOADING)
data SocketGetKeepaliveMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSocket a) => O.OverloadedMethod SocketGetKeepaliveMethodInfo a signature where
    overloadedMethod = socketGetKeepalive

instance O.OverloadedMethodInfo SocketGetKeepaliveMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketGetKeepalive",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketGetKeepalive"
        })


#endif

-- method Socket::get_listen_backlog
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_get_listen_backlog" g_socket_get_listen_backlog :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    IO Int32

-- | Gets the listen backlog setting of the socket. For details on this,
-- see 'GI.Gio.Objects.Socket.socketSetListenBacklog'.
-- 
-- /Since: 2.22/
socketGetListenBacklog ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> m Int32
    -- ^ __Returns:__ the maximum number of pending connections.
socketGetListenBacklog :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> m Int32
socketGetListenBacklog a
socket = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    result <- g_socket_get_listen_backlog socket'
    touchManagedPtr socket
    return result

#if defined(ENABLE_OVERLOADING)
data SocketGetListenBacklogMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsSocket a) => O.OverloadedMethod SocketGetListenBacklogMethodInfo a signature where
    overloadedMethod = socketGetListenBacklog

instance O.OverloadedMethodInfo SocketGetListenBacklogMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketGetListenBacklog",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketGetListenBacklog"
        })


#endif

-- method Socket::get_local_address
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "SocketAddress" })
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_get_local_address" g_socket_get_local_address :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Gio.SocketAddress.SocketAddress)

-- | Try to get the local address of a bound socket. This is only
-- useful if the socket has been bound to a local address,
-- either explicitly or implicitly when connecting.
-- 
-- /Since: 2.22/
socketGetLocalAddress ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> m Gio.SocketAddress.SocketAddress
    -- ^ __Returns:__ a t'GI.Gio.Objects.SocketAddress.SocketAddress' or 'P.Nothing' on error.
    --     Free the returned object with 'GI.GObject.Objects.Object.objectUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
socketGetLocalAddress :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> m SocketAddress
socketGetLocalAddress a
socket = IO SocketAddress -> m SocketAddress
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SocketAddress -> m SocketAddress)
-> IO SocketAddress -> m SocketAddress
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    onException (do
        result <- propagateGError $ g_socket_get_local_address socket'
        checkUnexpectedReturnNULL "socketGetLocalAddress" result
        result' <- (wrapObject Gio.SocketAddress.SocketAddress) result
        touchManagedPtr socket
        return result'
     ) (do
        return ()
     )

#if defined(ENABLE_OVERLOADING)
data SocketGetLocalAddressMethodInfo
instance (signature ~ (m Gio.SocketAddress.SocketAddress), MonadIO m, IsSocket a) => O.OverloadedMethod SocketGetLocalAddressMethodInfo a signature where
    overloadedMethod = socketGetLocalAddress

instance O.OverloadedMethodInfo SocketGetLocalAddressMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketGetLocalAddress",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketGetLocalAddress"
        })


#endif

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

foreign import ccall "g_socket_get_multicast_loopback" g_socket_get_multicast_loopback :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    IO CInt

-- | Gets the multicast loopback setting on /@socket@/; if 'P.True' (the
-- default), outgoing multicast packets will be looped back to
-- multicast listeners on the same host.
-- 
-- /Since: 2.32/
socketGetMulticastLoopback ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> m Bool
    -- ^ __Returns:__ the multicast loopback setting on /@socket@/
socketGetMulticastLoopback :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> m Bool
socketGetMulticastLoopback a
socket = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    result <- g_socket_get_multicast_loopback socket'
    let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    touchManagedPtr socket
    return result'

#if defined(ENABLE_OVERLOADING)
data SocketGetMulticastLoopbackMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSocket a) => O.OverloadedMethod SocketGetMulticastLoopbackMethodInfo a signature where
    overloadedMethod = socketGetMulticastLoopback

instance O.OverloadedMethodInfo SocketGetMulticastLoopbackMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketGetMulticastLoopback",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketGetMulticastLoopback"
        })


#endif

-- method Socket::get_multicast_ttl
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_get_multicast_ttl" g_socket_get_multicast_ttl :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    IO Word32

-- | Gets the multicast time-to-live setting on /@socket@/; see
-- 'GI.Gio.Objects.Socket.socketSetMulticastTtl' for more details.
-- 
-- /Since: 2.32/
socketGetMulticastTtl ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> m Word32
    -- ^ __Returns:__ the multicast time-to-live setting on /@socket@/
socketGetMulticastTtl :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> m Word32
socketGetMulticastTtl a
socket = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    result <- g_socket_get_multicast_ttl socket'
    touchManagedPtr socket
    return result

#if defined(ENABLE_OVERLOADING)
data SocketGetMulticastTtlMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSocket a) => O.OverloadedMethod SocketGetMulticastTtlMethodInfo a signature where
    overloadedMethod = socketGetMulticastTtl

instance O.OverloadedMethodInfo SocketGetMulticastTtlMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketGetMulticastTtl",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketGetMulticastTtl"
        })


#endif

-- method Socket::get_option
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "level"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the \"API level\" of the option (eg, `SOL_SOCKET`)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "optname"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the \"name\" of the option (eg, `SO_BROADCAST`)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the option value"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_get_option" g_socket_get_option :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Int32 ->                                -- level : TBasicType TInt
    Int32 ->                                -- optname : TBasicType TInt
    Ptr Int32 ->                            -- value : TBasicType TInt
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Gets the value of an integer-valued option on /@socket@/, as with
-- @/getsockopt()/@. (If you need to fetch a  non-integer-valued option,
-- you will need to call @/getsockopt()/@ directly.)
-- 
-- The [\<gio\/gnetworking.h>][gio-gnetworking.h]
-- header pulls in system headers that will define most of the
-- standard\/portable socket options. For unusual socket protocols or
-- platform-dependent options, you may need to include additional
-- headers.
-- 
-- Note that even for socket options that are a single byte in size,
-- /@value@/ is still a pointer to a @/gint/@ variable, not a @/guchar/@;
-- 'GI.Gio.Objects.Socket.socketGetOption' will handle the conversion internally.
-- 
-- /Since: 2.36/
socketGetOption ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'
    -> Int32
    -- ^ /@level@/: the \"API level\" of the option (eg, @SOL_SOCKET@)
    -> Int32
    -- ^ /@optname@/: the \"name\" of the option (eg, @SO_BROADCAST@)
    -> m (Int32)
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
socketGetOption :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> Int32 -> Int32 -> m Int32
socketGetOption a
socket Int32
level Int32
optname = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    value <- allocMem :: IO (Ptr Int32)
    onException (do
        _ <- propagateGError $ g_socket_get_option socket' level optname value
        value' <- peek value
        touchManagedPtr socket
        freeMem value
        return value'
     ) (do
        freeMem value
     )

#if defined(ENABLE_OVERLOADING)
data SocketGetOptionMethodInfo
instance (signature ~ (Int32 -> Int32 -> m (Int32)), MonadIO m, IsSocket a) => O.OverloadedMethod SocketGetOptionMethodInfo a signature where
    overloadedMethod = socketGetOption

instance O.OverloadedMethodInfo SocketGetOptionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketGetOption",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketGetOption"
        })


#endif

-- method Socket::get_protocol
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "SocketProtocol" })
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_get_protocol" g_socket_get_protocol :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    IO CInt

-- | Gets the socket protocol id the socket was created with.
-- In case the protocol is unknown, -1 is returned.
-- 
-- /Since: 2.22/
socketGetProtocol ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> m Gio.Enums.SocketProtocol
    -- ^ __Returns:__ a protocol id, or -1 if unknown
socketGetProtocol :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> m SocketProtocol
socketGetProtocol a
socket = IO SocketProtocol -> m SocketProtocol
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SocketProtocol -> m SocketProtocol)
-> IO SocketProtocol -> m SocketProtocol
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    result <- g_socket_get_protocol socket'
    let result' = (Int -> SocketProtocol
forall a. Enum a => Int -> a
toEnum (Int -> SocketProtocol) -> (CInt -> Int) -> CInt -> SocketProtocol
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CInt
result
    touchManagedPtr socket
    return result'

#if defined(ENABLE_OVERLOADING)
data SocketGetProtocolMethodInfo
instance (signature ~ (m Gio.Enums.SocketProtocol), MonadIO m, IsSocket a) => O.OverloadedMethod SocketGetProtocolMethodInfo a signature where
    overloadedMethod = socketGetProtocol

instance O.OverloadedMethodInfo SocketGetProtocolMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketGetProtocol",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketGetProtocol"
        })


#endif

-- method Socket::get_remote_address
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "SocketAddress" })
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_get_remote_address" g_socket_get_remote_address :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Gio.SocketAddress.SocketAddress)

-- | Try to get the remote address of a connected socket. This is only
-- useful for connection oriented sockets that have been connected.
-- 
-- /Since: 2.22/
socketGetRemoteAddress ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> m Gio.SocketAddress.SocketAddress
    -- ^ __Returns:__ a t'GI.Gio.Objects.SocketAddress.SocketAddress' or 'P.Nothing' on error.
    --     Free the returned object with 'GI.GObject.Objects.Object.objectUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
socketGetRemoteAddress :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> m SocketAddress
socketGetRemoteAddress a
socket = IO SocketAddress -> m SocketAddress
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SocketAddress -> m SocketAddress)
-> IO SocketAddress -> m SocketAddress
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    onException (do
        result <- propagateGError $ g_socket_get_remote_address socket'
        checkUnexpectedReturnNULL "socketGetRemoteAddress" result
        result' <- (wrapObject Gio.SocketAddress.SocketAddress) result
        touchManagedPtr socket
        return result'
     ) (do
        return ()
     )

#if defined(ENABLE_OVERLOADING)
data SocketGetRemoteAddressMethodInfo
instance (signature ~ (m Gio.SocketAddress.SocketAddress), MonadIO m, IsSocket a) => O.OverloadedMethod SocketGetRemoteAddressMethodInfo a signature where
    overloadedMethod = socketGetRemoteAddress

instance O.OverloadedMethodInfo SocketGetRemoteAddressMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketGetRemoteAddress",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketGetRemoteAddress"
        })


#endif

-- method Socket::get_socket_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "SocketType" })
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_get_socket_type" g_socket_get_socket_type :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    IO CUInt

-- | Gets the socket type of the socket.
-- 
-- /Since: 2.22/
socketGetSocketType ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> m Gio.Enums.SocketType
    -- ^ __Returns:__ a t'GI.Gio.Enums.SocketType'
socketGetSocketType :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> m SocketType
socketGetSocketType a
socket = IO SocketType -> m SocketType
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SocketType -> m SocketType) -> IO SocketType -> m SocketType
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    result <- g_socket_get_socket_type socket'
    let result' = (Int -> SocketType
forall a. Enum a => Int -> a
toEnum (Int -> SocketType) -> (CUInt -> Int) -> CUInt -> SocketType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    touchManagedPtr socket
    return result'

#if defined(ENABLE_OVERLOADING)
data SocketGetSocketTypeMethodInfo
instance (signature ~ (m Gio.Enums.SocketType), MonadIO m, IsSocket a) => O.OverloadedMethod SocketGetSocketTypeMethodInfo a signature where
    overloadedMethod = socketGetSocketType

instance O.OverloadedMethodInfo SocketGetSocketTypeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketGetSocketType",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketGetSocketType"
        })


#endif

-- method Socket::get_timeout
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_get_timeout" g_socket_get_timeout :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    IO Word32

-- | Gets the timeout setting of the socket. For details on this, see
-- 'GI.Gio.Objects.Socket.socketSetTimeout'.
-- 
-- /Since: 2.26/
socketGetTimeout ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> m Word32
    -- ^ __Returns:__ the timeout in seconds
socketGetTimeout :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> m Word32
socketGetTimeout a
socket = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    result <- g_socket_get_timeout socket'
    touchManagedPtr socket
    return result

#if defined(ENABLE_OVERLOADING)
data SocketGetTimeoutMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSocket a) => O.OverloadedMethod SocketGetTimeoutMethodInfo a signature where
    overloadedMethod = socketGetTimeout

instance O.OverloadedMethodInfo SocketGetTimeoutMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketGetTimeout",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketGetTimeout"
        })


#endif

-- method Socket::get_ttl
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_get_ttl" g_socket_get_ttl :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    IO Word32

-- | Gets the unicast time-to-live setting on /@socket@/; see
-- 'GI.Gio.Objects.Socket.socketSetTtl' for more details.
-- 
-- /Since: 2.32/
socketGetTtl ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> m Word32
    -- ^ __Returns:__ the time-to-live setting on /@socket@/
socketGetTtl :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> m Word32
socketGetTtl a
socket = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    result <- g_socket_get_ttl socket'
    touchManagedPtr socket
    return result

#if defined(ENABLE_OVERLOADING)
data SocketGetTtlMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSocket a) => O.OverloadedMethod SocketGetTtlMethodInfo a signature where
    overloadedMethod = socketGetTtl

instance O.OverloadedMethodInfo SocketGetTtlMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketGetTtl",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketGetTtl"
        })


#endif

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

foreign import ccall "g_socket_is_closed" g_socket_is_closed :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    IO CInt

-- | Checks whether a socket is closed.
-- 
-- /Since: 2.22/
socketIsClosed ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if socket is closed, 'P.False' otherwise
socketIsClosed :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> m Bool
socketIsClosed a
socket = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    result <- g_socket_is_closed socket'
    let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    touchManagedPtr socket
    return result'

#if defined(ENABLE_OVERLOADING)
data SocketIsClosedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSocket a) => O.OverloadedMethod SocketIsClosedMethodInfo a signature where
    overloadedMethod = socketIsClosed

instance O.OverloadedMethodInfo SocketIsClosedMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketIsClosed",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketIsClosed"
        })


#endif

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

foreign import ccall "g_socket_is_connected" g_socket_is_connected :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    IO CInt

-- | Check whether the socket is connected. This is only useful for
-- connection-oriented sockets.
-- 
-- If using 'GI.Gio.Objects.Socket.socketShutdown', this function will return 'P.True' until the
-- socket has been shut down for reading and writing. If you do a non-blocking
-- connect, this function will not return 'P.True' until after you call
-- 'GI.Gio.Objects.Socket.socketCheckConnectResult'.
-- 
-- /Since: 2.22/
socketIsConnected ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if socket is connected, 'P.False' otherwise.
socketIsConnected :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> m Bool
socketIsConnected a
socket = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    result <- g_socket_is_connected socket'
    let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    touchManagedPtr socket
    return result'

#if defined(ENABLE_OVERLOADING)
data SocketIsConnectedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSocket a) => O.OverloadedMethod SocketIsConnectedMethodInfo a signature where
    overloadedMethod = socketIsConnected

instance O.OverloadedMethodInfo SocketIsConnectedMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketIsConnected",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketIsConnected"
        })


#endif

-- method Socket::join_multicast_group
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "InetAddress" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GInetAddress specifying the group address to join."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "source_specific"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "%TRUE if source-specific multicast should be used"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "iface"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Name of the interface to use, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_join_multicast_group" g_socket_join_multicast_group :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Ptr Gio.InetAddress.InetAddress ->      -- group : TInterface (Name {namespace = "Gio", name = "InetAddress"})
    CInt ->                                 -- source_specific : TBasicType TBoolean
    CString ->                              -- iface : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Registers /@socket@/ to receive multicast messages sent to /@group@/.
-- /@socket@/ must be a 'GI.Gio.Enums.SocketTypeDatagram' socket, and must have
-- been bound to an appropriate interface and port with
-- 'GI.Gio.Objects.Socket.socketBind'.
-- 
-- If /@iface@/ is 'P.Nothing', the system will automatically pick an interface
-- to bind to based on /@group@/.
-- 
-- If /@sourceSpecific@/ is 'P.True', source-specific multicast as defined
-- in RFC 4604 is used. Note that on older platforms this may fail
-- with a 'GI.Gio.Enums.IOErrorEnumNotSupported' error.
-- 
-- To bind to a given source-specific multicast address, use
-- 'GI.Gio.Objects.Socket.socketJoinMulticastGroupSsm' instead.
-- 
-- /Since: 2.32/
socketJoinMulticastGroup ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.InetAddress.IsInetAddress b) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> b
    -- ^ /@group@/: a t'GI.Gio.Objects.InetAddress.InetAddress' specifying the group address to join.
    -> Bool
    -- ^ /@sourceSpecific@/: 'P.True' if source-specific multicast should be used
    -> Maybe (T.Text)
    -- ^ /@iface@/: Name of the interface to use, or 'P.Nothing'
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
socketJoinMulticastGroup :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSocket a, IsInetAddress b) =>
a -> b -> Bool -> Maybe Text -> m ()
socketJoinMulticastGroup a
socket b
group Bool
sourceSpecific Maybe Text
iface = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    group' <- unsafeManagedPtrCastPtr group
    let sourceSpecific' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
sourceSpecific
    maybeIface <- case iface of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
FP.nullPtr
        Just Text
jIface -> do
            jIface' <- Text -> IO (Ptr CChar)
textToCString Text
jIface
            return jIface'
    onException (do
        _ <- propagateGError $ g_socket_join_multicast_group socket' group' sourceSpecific' maybeIface
        touchManagedPtr socket
        touchManagedPtr group
        freeMem maybeIface
        return ()
     ) (do
        freeMem maybeIface
     )

#if defined(ENABLE_OVERLOADING)
data SocketJoinMulticastGroupMethodInfo
instance (signature ~ (b -> Bool -> Maybe (T.Text) -> m ()), MonadIO m, IsSocket a, Gio.InetAddress.IsInetAddress b) => O.OverloadedMethod SocketJoinMulticastGroupMethodInfo a signature where
    overloadedMethod = socketJoinMulticastGroup

instance O.OverloadedMethodInfo SocketJoinMulticastGroupMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketJoinMulticastGroup",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketJoinMulticastGroup"
        })


#endif

-- method Socket::join_multicast_group_ssm
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "InetAddress" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GInetAddress specifying the group address to join."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "source_specific"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "InetAddress" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a #GInetAddress specifying the\nsource-specific multicast address or %NULL to ignore."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "iface"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Name of the interface to use, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_join_multicast_group_ssm" g_socket_join_multicast_group_ssm :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Ptr Gio.InetAddress.InetAddress ->      -- group : TInterface (Name {namespace = "Gio", name = "InetAddress"})
    Ptr Gio.InetAddress.InetAddress ->      -- source_specific : TInterface (Name {namespace = "Gio", name = "InetAddress"})
    CString ->                              -- iface : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Registers /@socket@/ to receive multicast messages sent to /@group@/.
-- /@socket@/ must be a 'GI.Gio.Enums.SocketTypeDatagram' socket, and must have
-- been bound to an appropriate interface and port with
-- 'GI.Gio.Objects.Socket.socketBind'.
-- 
-- If /@iface@/ is 'P.Nothing', the system will automatically pick an interface
-- to bind to based on /@group@/.
-- 
-- If /@sourceSpecific@/ is not 'P.Nothing', use source-specific multicast as
-- defined in RFC 4604. Note that on older platforms this may fail
-- with a 'GI.Gio.Enums.IOErrorEnumNotSupported' error.
-- 
-- Note that this function can be called multiple times for the same
-- /@group@/ with different /@sourceSpecific@/ in order to receive multicast
-- packets from more than one source.
-- 
-- /Since: 2.56/
socketJoinMulticastGroupSsm ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.InetAddress.IsInetAddress b, Gio.InetAddress.IsInetAddress c) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> b
    -- ^ /@group@/: a t'GI.Gio.Objects.InetAddress.InetAddress' specifying the group address to join.
    -> Maybe (c)
    -- ^ /@sourceSpecific@/: a t'GI.Gio.Objects.InetAddress.InetAddress' specifying the
    -- source-specific multicast address or 'P.Nothing' to ignore.
    -> Maybe (T.Text)
    -- ^ /@iface@/: Name of the interface to use, or 'P.Nothing'
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
socketJoinMulticastGroupSsm :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsSocket a, IsInetAddress b,
 IsInetAddress c) =>
a -> b -> Maybe c -> Maybe Text -> m ()
socketJoinMulticastGroupSsm a
socket b
group Maybe c
sourceSpecific Maybe Text
iface = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    group' <- unsafeManagedPtrCastPtr group
    maybeSourceSpecific <- case sourceSpecific of
        Maybe c
Nothing -> Ptr InetAddress -> IO (Ptr InetAddress)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr InetAddress
forall a. Ptr a
FP.nullPtr
        Just c
jSourceSpecific -> do
            jSourceSpecific' <- c -> IO (Ptr InetAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jSourceSpecific
            return jSourceSpecific'
    maybeIface <- case iface of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
FP.nullPtr
        Just Text
jIface -> do
            jIface' <- Text -> IO (Ptr CChar)
textToCString Text
jIface
            return jIface'
    onException (do
        _ <- propagateGError $ g_socket_join_multicast_group_ssm socket' group' maybeSourceSpecific maybeIface
        touchManagedPtr socket
        touchManagedPtr group
        whenJust sourceSpecific touchManagedPtr
        freeMem maybeIface
        return ()
     ) (do
        freeMem maybeIface
     )

#if defined(ENABLE_OVERLOADING)
data SocketJoinMulticastGroupSsmMethodInfo
instance (signature ~ (b -> Maybe (c) -> Maybe (T.Text) -> m ()), MonadIO m, IsSocket a, Gio.InetAddress.IsInetAddress b, Gio.InetAddress.IsInetAddress c) => O.OverloadedMethod SocketJoinMulticastGroupSsmMethodInfo a signature where
    overloadedMethod = socketJoinMulticastGroupSsm

instance O.OverloadedMethodInfo SocketJoinMulticastGroupSsmMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketJoinMulticastGroupSsm",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketJoinMulticastGroupSsm"
        })


#endif

-- method Socket::leave_multicast_group
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "InetAddress" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GInetAddress specifying the group address to leave."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "source_specific"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "%TRUE if source-specific multicast was used"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "iface"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Interface used" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_leave_multicast_group" g_socket_leave_multicast_group :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Ptr Gio.InetAddress.InetAddress ->      -- group : TInterface (Name {namespace = "Gio", name = "InetAddress"})
    CInt ->                                 -- source_specific : TBasicType TBoolean
    CString ->                              -- iface : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Removes /@socket@/ from the multicast group defined by /@group@/, /@iface@/,
-- and /@sourceSpecific@/ (which must all have the same values they had
-- when you joined the group).
-- 
-- /@socket@/ remains bound to its address and port, and can still receive
-- unicast messages after calling this.
-- 
-- To unbind to a given source-specific multicast address, use
-- 'GI.Gio.Objects.Socket.socketLeaveMulticastGroupSsm' instead.
-- 
-- /Since: 2.32/
socketLeaveMulticastGroup ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.InetAddress.IsInetAddress b) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> b
    -- ^ /@group@/: a t'GI.Gio.Objects.InetAddress.InetAddress' specifying the group address to leave.
    -> Bool
    -- ^ /@sourceSpecific@/: 'P.True' if source-specific multicast was used
    -> Maybe (T.Text)
    -- ^ /@iface@/: Interface used
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
socketLeaveMulticastGroup :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSocket a, IsInetAddress b) =>
a -> b -> Bool -> Maybe Text -> m ()
socketLeaveMulticastGroup a
socket b
group Bool
sourceSpecific Maybe Text
iface = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    group' <- unsafeManagedPtrCastPtr group
    let sourceSpecific' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
sourceSpecific
    maybeIface <- case iface of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
FP.nullPtr
        Just Text
jIface -> do
            jIface' <- Text -> IO (Ptr CChar)
textToCString Text
jIface
            return jIface'
    onException (do
        _ <- propagateGError $ g_socket_leave_multicast_group socket' group' sourceSpecific' maybeIface
        touchManagedPtr socket
        touchManagedPtr group
        freeMem maybeIface
        return ()
     ) (do
        freeMem maybeIface
     )

#if defined(ENABLE_OVERLOADING)
data SocketLeaveMulticastGroupMethodInfo
instance (signature ~ (b -> Bool -> Maybe (T.Text) -> m ()), MonadIO m, IsSocket a, Gio.InetAddress.IsInetAddress b) => O.OverloadedMethod SocketLeaveMulticastGroupMethodInfo a signature where
    overloadedMethod = socketLeaveMulticastGroup

instance O.OverloadedMethodInfo SocketLeaveMulticastGroupMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketLeaveMulticastGroup",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketLeaveMulticastGroup"
        })


#endif

-- method Socket::leave_multicast_group_ssm
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "InetAddress" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GInetAddress specifying the group address to leave."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "source_specific"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "InetAddress" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a #GInetAddress specifying the\nsource-specific multicast address or %NULL to ignore."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "iface"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Name of the interface to use, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_leave_multicast_group_ssm" g_socket_leave_multicast_group_ssm :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Ptr Gio.InetAddress.InetAddress ->      -- group : TInterface (Name {namespace = "Gio", name = "InetAddress"})
    Ptr Gio.InetAddress.InetAddress ->      -- source_specific : TInterface (Name {namespace = "Gio", name = "InetAddress"})
    CString ->                              -- iface : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Removes /@socket@/ from the multicast group defined by /@group@/, /@iface@/,
-- and /@sourceSpecific@/ (which must all have the same values they had
-- when you joined the group).
-- 
-- /@socket@/ remains bound to its address and port, and can still receive
-- unicast messages after calling this.
-- 
-- /Since: 2.56/
socketLeaveMulticastGroupSsm ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.InetAddress.IsInetAddress b, Gio.InetAddress.IsInetAddress c) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> b
    -- ^ /@group@/: a t'GI.Gio.Objects.InetAddress.InetAddress' specifying the group address to leave.
    -> Maybe (c)
    -- ^ /@sourceSpecific@/: a t'GI.Gio.Objects.InetAddress.InetAddress' specifying the
    -- source-specific multicast address or 'P.Nothing' to ignore.
    -> Maybe (T.Text)
    -- ^ /@iface@/: Name of the interface to use, or 'P.Nothing'
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
socketLeaveMulticastGroupSsm :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsSocket a, IsInetAddress b,
 IsInetAddress c) =>
a -> b -> Maybe c -> Maybe Text -> m ()
socketLeaveMulticastGroupSsm a
socket b
group Maybe c
sourceSpecific Maybe Text
iface = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    group' <- unsafeManagedPtrCastPtr group
    maybeSourceSpecific <- case sourceSpecific of
        Maybe c
Nothing -> Ptr InetAddress -> IO (Ptr InetAddress)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr InetAddress
forall a. Ptr a
FP.nullPtr
        Just c
jSourceSpecific -> do
            jSourceSpecific' <- c -> IO (Ptr InetAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jSourceSpecific
            return jSourceSpecific'
    maybeIface <- case iface of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
FP.nullPtr
        Just Text
jIface -> do
            jIface' <- Text -> IO (Ptr CChar)
textToCString Text
jIface
            return jIface'
    onException (do
        _ <- propagateGError $ g_socket_leave_multicast_group_ssm socket' group' maybeSourceSpecific maybeIface
        touchManagedPtr socket
        touchManagedPtr group
        whenJust sourceSpecific touchManagedPtr
        freeMem maybeIface
        return ()
     ) (do
        freeMem maybeIface
     )

#if defined(ENABLE_OVERLOADING)
data SocketLeaveMulticastGroupSsmMethodInfo
instance (signature ~ (b -> Maybe (c) -> Maybe (T.Text) -> m ()), MonadIO m, IsSocket a, Gio.InetAddress.IsInetAddress b, Gio.InetAddress.IsInetAddress c) => O.OverloadedMethod SocketLeaveMulticastGroupSsmMethodInfo a signature where
    overloadedMethod = socketLeaveMulticastGroupSsm

instance O.OverloadedMethodInfo SocketLeaveMulticastGroupSsmMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketLeaveMulticastGroupSsm",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketLeaveMulticastGroupSsm"
        })


#endif

-- method Socket::listen
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_listen" g_socket_listen :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Marks the socket as a server socket, i.e. a socket that is used
-- to accept incoming requests using 'GI.Gio.Objects.Socket.socketAccept'.
-- 
-- Before calling this the socket must be bound to a local address using
-- 'GI.Gio.Objects.Socket.socketBind'.
-- 
-- To set the maximum amount of outstanding clients, use
-- 'GI.Gio.Objects.Socket.socketSetListenBacklog'.
-- 
-- /Since: 2.22/
socketListen ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
socketListen :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> m ()
socketListen a
socket = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    onException (do
        _ <- propagateGError $ g_socket_listen socket'
        touchManagedPtr socket
        return ()
     ) (do
        return ()
     )

#if defined(ENABLE_OVERLOADING)
data SocketListenMethodInfo
instance (signature ~ (m ()), MonadIO m, IsSocket a) => O.OverloadedMethod SocketListenMethodInfo a signature where
    overloadedMethod = socketListen

instance O.OverloadedMethodInfo SocketListenMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketListen",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketListen"
        })


#endif

-- method Socket::receive
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "buffer"
--           , argType = TCArray False (-1) 2 (TBasicType TUInt8)
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "\n    a buffer to read data into (which should be at least @size bytes long)."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TSize
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the number of bytes you want to read from the socket"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a %GCancellable or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "size"
--              , argType = TBasicType TSize
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just "the number of bytes you want to read from the socket"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , argCallbackUserData = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just (TBasicType TSSize)
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_receive" g_socket_receive :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Ptr Word8 ->                            -- buffer : TCArray False (-1) 2 (TBasicType TUInt8)
    FCT.CSize ->                            -- size : TBasicType TSize
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO DI.Int64

-- | Receive data (up to /@size@/ bytes) from a socket. This is mainly used by
-- connection-oriented sockets; it is identical to 'GI.Gio.Objects.Socket.socketReceiveFrom'
-- with /@address@/ set to 'P.Nothing'.
-- 
-- For 'GI.Gio.Enums.SocketTypeDatagram' and 'GI.Gio.Enums.SocketTypeSeqpacket' sockets,
-- 'GI.Gio.Objects.Socket.socketReceive' will always read either 0 or 1 complete messages from
-- the socket. If the received message is too large to fit in /@buffer@/, then
-- the data beyond /@size@/ bytes will be discarded, without any explicit
-- indication that this has occurred.
-- 
-- For 'GI.Gio.Enums.SocketTypeStream' sockets, 'GI.Gio.Objects.Socket.socketReceive' can return any
-- number of bytes, up to /@size@/. If more than /@size@/ bytes have been
-- received, the additional data will be returned in future calls to
-- 'GI.Gio.Objects.Socket.socketReceive'.
-- 
-- If the socket is in blocking mode the call will block until there
-- is some data to receive, the connection is closed, or there is an
-- error. If there is no data available and the socket is in
-- non-blocking mode, a 'GI.Gio.Enums.IOErrorEnumWouldBlock' error will be
-- returned. To be notified when data is available, wait for the
-- 'GI.GObject.Flags.IOConditionIn' condition.
-- 
-- On error -1 is returned and /@error@/ is set accordingly.
-- 
-- /Since: 2.22/
socketReceive ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'
    -> ByteString
    -- ^ /@buffer@/: 
    --     a buffer to read data into (which should be at least /@size@/ bytes long).
    -> Maybe (b)
    -- ^ /@cancellable@/: a @/GCancellable/@ or 'P.Nothing'
    -> m ((DI.Int64, ByteString))
    -- ^ __Returns:__ Number of bytes read, or 0 if the connection was closed by
    -- the peer, or -1 on error /(Can throw 'Data.GI.Base.GError.GError')/
socketReceive :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSocket a, IsCancellable b) =>
a -> ByteString -> Maybe b -> m (Int64, ByteString)
socketReceive a
socket ByteString
buffer Maybe b
cancellable = IO (Int64, ByteString) -> m (Int64, ByteString)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int64, ByteString) -> m (Int64, ByteString))
-> IO (Int64, ByteString) -> m (Int64, ByteString)
forall a b. (a -> b) -> a -> b
$ do
    let size :: CSize
size = Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CSize) -> Int -> CSize
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
buffer
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    buffer' <- packByteString buffer
    maybeCancellable <- case cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just b
jCancellable -> do
            jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_socket_receive socket' buffer' size maybeCancellable
        buffer'' <- (unpackByteStringWithLength size) buffer'
        freeMem buffer'
        touchManagedPtr socket
        whenJust cancellable touchManagedPtr
        return (result, buffer'')
     ) (do
        freeMem buffer'
     )

#if defined(ENABLE_OVERLOADING)
data SocketReceiveMethodInfo
instance (signature ~ (ByteString -> Maybe (b) -> m ((DI.Int64, ByteString))), MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod SocketReceiveMethodInfo a signature where
    overloadedMethod = socketReceive

instance O.OverloadedMethodInfo SocketReceiveMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketReceive",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketReceive"
        })


#endif

-- method Socket::receive_bytes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TSize
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the number of bytes you want to read from the socket"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "timeout_us"
--           , argType = TBasicType TInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the timeout to wait for, in microseconds, or `-1` to block\n  indefinitely"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a %GCancellable, or `NULL`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "Bytes" })
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_receive_bytes" g_socket_receive_bytes :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    FCT.CSize ->                            -- size : TBasicType TSize
    Int64 ->                                -- timeout_us : TBasicType TInt64
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr GLib.Bytes.Bytes)

-- | Receives data (up to /@size@/ bytes) from a socket.
-- 
-- This function is a variant of 'GI.Gio.Objects.Socket.socketReceive' which returns a
-- [struct/@gLib@/.Bytes] rather than a plain buffer.
-- 
-- Pass @-1@ to /@timeoutUs@/ to block indefinitely until data is received (or
-- the connection is closed, or there is an error). Pass @0@ to use the default
-- timeout from [Socket:timeout]("GI.Gio.Objects.Socket#g:attr:timeout"), or pass a positive number to wait
-- for that many microseconds for data before returning @G_IO_ERROR_TIMED_OUT@.
-- 
-- /Since: 2.80/
socketReceiveBytes ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'
    -> FCT.CSize
    -- ^ /@size@/: the number of bytes you want to read from the socket
    -> Int64
    -- ^ /@timeoutUs@/: the timeout to wait for, in microseconds, or @-1@ to block
    --   indefinitely
    -> Maybe (b)
    -- ^ /@cancellable@/: a @/GCancellable/@, or @NULL@
    -> m GLib.Bytes.Bytes
    -- ^ __Returns:__ a bytes buffer containing the
    --   received bytes, or @NULL@ on error /(Can throw 'Data.GI.Base.GError.GError')/
socketReceiveBytes :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSocket a, IsCancellable b) =>
a -> CSize -> Int64 -> Maybe b -> m Bytes
socketReceiveBytes a
socket CSize
size Int64
timeoutUs Maybe b
cancellable = IO Bytes -> m Bytes
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bytes -> m Bytes) -> IO Bytes -> m Bytes
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    maybeCancellable <- case cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just b
jCancellable -> do
            jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_socket_receive_bytes socket' size timeoutUs maybeCancellable
        checkUnexpectedReturnNULL "socketReceiveBytes" result
        result' <- (wrapBoxed GLib.Bytes.Bytes) result
        touchManagedPtr socket
        whenJust cancellable touchManagedPtr
        return result'
     ) (do
        return ()
     )

#if defined(ENABLE_OVERLOADING)
data SocketReceiveBytesMethodInfo
instance (signature ~ (FCT.CSize -> Int64 -> Maybe (b) -> m GLib.Bytes.Bytes), MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod SocketReceiveBytesMethodInfo a signature where
    overloadedMethod = socketReceiveBytes

instance O.OverloadedMethodInfo SocketReceiveBytesMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketReceiveBytes",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketReceiveBytes"
        })


#endif

-- method Socket::receive_bytes_from
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "address"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SocketAddress" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for a #GSocketAddress"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TSize
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the number of bytes you want to read from the socket"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "timeout_us"
--           , argType = TBasicType TInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the timeout to wait for, in microseconds, or `-1` to block\n  indefinitely"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GCancellable, or `NULL`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "Bytes" })
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_receive_bytes_from" g_socket_receive_bytes_from :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Ptr (Ptr Gio.SocketAddress.SocketAddress) -> -- address : TInterface (Name {namespace = "Gio", name = "SocketAddress"})
    FCT.CSize ->                            -- size : TBasicType TSize
    Int64 ->                                -- timeout_us : TBasicType TInt64
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr GLib.Bytes.Bytes)

-- | Receive data (up to /@size@/ bytes) from a socket.
-- 
-- This function is a variant of 'GI.Gio.Objects.Socket.socketReceiveFrom' which returns
-- a [struct/@gLib@/.Bytes] rather than a plain buffer.
-- 
-- If /@address@/ is non-'P.Nothing' then /@address@/ will be set equal to the
-- source address of the received packet.
-- 
-- The /@address@/ is owned by the caller.
-- 
-- Pass @-1@ to /@timeoutUs@/ to block indefinitely until data is received (or
-- the connection is closed, or there is an error). Pass @0@ to use the default
-- timeout from [Socket:timeout]("GI.Gio.Objects.Socket#g:attr:timeout"), or pass a positive number to wait
-- for that many microseconds for data before returning @G_IO_ERROR_TIMED_OUT@.
-- 
-- /Since: 2.80/
socketReceiveBytesFrom ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'
    -> FCT.CSize
    -- ^ /@size@/: the number of bytes you want to read from the socket
    -> Int64
    -- ^ /@timeoutUs@/: the timeout to wait for, in microseconds, or @-1@ to block
    --   indefinitely
    -> Maybe (b)
    -- ^ /@cancellable@/: a t'GI.Gio.Objects.Cancellable.Cancellable', or @NULL@
    -> m ((GLib.Bytes.Bytes, Gio.SocketAddress.SocketAddress))
    -- ^ __Returns:__ a bytes buffer containing the
    --   received bytes, or @NULL@ on error /(Can throw 'Data.GI.Base.GError.GError')/
socketReceiveBytesFrom :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSocket a, IsCancellable b) =>
a -> CSize -> Int64 -> Maybe b -> m (Bytes, SocketAddress)
socketReceiveBytesFrom a
socket CSize
size Int64
timeoutUs Maybe b
cancellable = IO (Bytes, SocketAddress) -> m (Bytes, SocketAddress)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bytes, SocketAddress) -> m (Bytes, SocketAddress))
-> IO (Bytes, SocketAddress) -> m (Bytes, SocketAddress)
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    address <- callocMem :: IO (Ptr (Ptr Gio.SocketAddress.SocketAddress))
    maybeCancellable <- case cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just b
jCancellable -> do
            jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_socket_receive_bytes_from socket' address size timeoutUs maybeCancellable
        checkUnexpectedReturnNULL "socketReceiveBytesFrom" result
        result' <- (wrapBoxed GLib.Bytes.Bytes) result
        address' <- peek address
        address'' <- (wrapObject Gio.SocketAddress.SocketAddress) address'
        touchManagedPtr socket
        whenJust cancellable touchManagedPtr
        freeMem address
        return (result', address'')
     ) (do
        freeMem address
     )

#if defined(ENABLE_OVERLOADING)
data SocketReceiveBytesFromMethodInfo
instance (signature ~ (FCT.CSize -> Int64 -> Maybe (b) -> m ((GLib.Bytes.Bytes, Gio.SocketAddress.SocketAddress))), MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod SocketReceiveBytesFromMethodInfo a signature where
    overloadedMethod = socketReceiveBytesFrom

instance O.OverloadedMethodInfo SocketReceiveBytesFromMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketReceiveBytesFrom",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketReceiveBytesFrom"
        })


#endif

-- method Socket::receive_from
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "address"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SocketAddress" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a pointer to a #GSocketAddress\n    pointer, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "buffer"
--           , argType = TCArray False (-1) 3 (TBasicType TUInt8)
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "\n    a buffer to read data into (which should be at least @size bytes long)."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TSize
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the number of bytes you want to read from the socket"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a %GCancellable or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "size"
--              , argType = TBasicType TSize
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just "the number of bytes you want to read from the socket"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , argCallbackUserData = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just (TBasicType TSSize)
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_receive_from" g_socket_receive_from :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Ptr (Ptr Gio.SocketAddress.SocketAddress) -> -- address : TInterface (Name {namespace = "Gio", name = "SocketAddress"})
    Ptr Word8 ->                            -- buffer : TCArray False (-1) 3 (TBasicType TUInt8)
    FCT.CSize ->                            -- size : TBasicType TSize
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO DI.Int64

-- | Receive data (up to /@size@/ bytes) from a socket.
-- 
-- If /@address@/ is non-'P.Nothing' then /@address@/ will be set equal to the
-- source address of the received packet.
-- /@address@/ is owned by the caller.
-- 
-- See 'GI.Gio.Objects.Socket.socketReceive' for additional information.
-- 
-- /Since: 2.22/
socketReceiveFrom ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'
    -> ByteString
    -- ^ /@buffer@/: 
    --     a buffer to read data into (which should be at least /@size@/ bytes long).
    -> Maybe (b)
    -- ^ /@cancellable@/: a @/GCancellable/@ or 'P.Nothing'
    -> m ((DI.Int64, Gio.SocketAddress.SocketAddress, ByteString))
    -- ^ __Returns:__ Number of bytes read, or 0 if the connection was closed by
    -- the peer, or -1 on error /(Can throw 'Data.GI.Base.GError.GError')/
socketReceiveFrom :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSocket a, IsCancellable b) =>
a -> ByteString -> Maybe b -> m (Int64, SocketAddress, ByteString)
socketReceiveFrom a
socket ByteString
buffer Maybe b
cancellable = IO (Int64, SocketAddress, ByteString)
-> m (Int64, SocketAddress, ByteString)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int64, SocketAddress, ByteString)
 -> m (Int64, SocketAddress, ByteString))
-> IO (Int64, SocketAddress, ByteString)
-> m (Int64, SocketAddress, ByteString)
forall a b. (a -> b) -> a -> b
$ do
    let size :: CSize
size = Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CSize) -> Int -> CSize
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
buffer
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    address <- callocMem :: IO (Ptr (Ptr Gio.SocketAddress.SocketAddress))
    buffer' <- packByteString buffer
    maybeCancellable <- case cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just b
jCancellable -> do
            jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_socket_receive_from socket' address buffer' size maybeCancellable
        address' <- peek address
        address'' <- (wrapObject Gio.SocketAddress.SocketAddress) address'
        buffer'' <- (unpackByteStringWithLength size) buffer'
        freeMem buffer'
        touchManagedPtr socket
        whenJust cancellable touchManagedPtr
        freeMem address
        return (result, address'', buffer'')
     ) (do
        freeMem address
        freeMem buffer'
     )

#if defined(ENABLE_OVERLOADING)
data SocketReceiveFromMethodInfo
instance (signature ~ (ByteString -> Maybe (b) -> m ((DI.Int64, Gio.SocketAddress.SocketAddress, ByteString))), MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod SocketReceiveFromMethodInfo a signature where
    overloadedMethod = socketReceiveFrom

instance O.OverloadedMethodInfo SocketReceiveFromMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketReceiveFrom",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketReceiveFrom"
        })


#endif

-- method Socket::receive_message
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "address"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SocketAddress" }
--           , direction = DirectionOut
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a pointer to a #GSocketAddress\n    pointer, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "vectors"
--           , argType =
--               TCArray
--                 False
--                 (-1)
--                 3
--                 (TInterface Name { namespace = "Gio" , name = "InputVector" })
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an array of #GInputVector structs"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "num_vectors"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of elements in @vectors, or -1"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "messages"
--           , argType =
--               TCArray
--                 False
--                 (-1)
--                 5
--                 (TInterface
--                    Name { namespace = "Gio" , name = "SocketControlMessage" })
--           , direction = DirectionOut
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a pointer\n   which may be filled with an array of #GSocketControlMessages, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "num_messages"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a pointer which will be filled with the number of\n   elements in @messages, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "flags"
--           , argType = TBasicType TInt
--           , direction = DirectionInout
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a pointer to an int containing #GSocketMsgFlags flags,\n   which may additionally contain\n   [other platform specific flags](http://man7.org/linux/man-pages/man2/recv.2.html)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a %GCancellable or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "num_messages"
--              , argType = TBasicType TInt
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just
--                          "a pointer which will be filled with the number of\n   elements in @messages, or %NULL"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , argCallbackUserData = False
--              , transfer = TransferEverything
--              }
--          , Arg
--              { argCName = "num_vectors"
--              , argType = TBasicType TInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "the number of elements in @vectors, or -1"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , argCallbackUserData = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just (TBasicType TSSize)
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_receive_message" g_socket_receive_message :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Ptr (Ptr Gio.SocketAddress.SocketAddress) -> -- address : TInterface (Name {namespace = "Gio", name = "SocketAddress"})
    Ptr Gio.InputVector.InputVector ->      -- vectors : TCArray False (-1) 3 (TInterface (Name {namespace = "Gio", name = "InputVector"}))
    Int32 ->                                -- num_vectors : TBasicType TInt
    Ptr (Ptr (Ptr Gio.SocketControlMessage.SocketControlMessage)) -> -- messages : TCArray False (-1) 5 (TInterface (Name {namespace = "Gio", name = "SocketControlMessage"}))
    Ptr Int32 ->                            -- num_messages : TBasicType TInt
    Ptr Int32 ->                            -- flags : TBasicType TInt
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO DI.Int64

-- | Receive data from a socket.  For receiving multiple messages, see
-- 'GI.Gio.Objects.Socket.socketReceiveMessages'; for easier use, see
-- 'GI.Gio.Objects.Socket.socketReceive' and 'GI.Gio.Objects.Socket.socketReceiveFrom'.
-- 
-- If /@address@/ is non-'P.Nothing' then /@address@/ will be set equal to the
-- source address of the received packet.
-- /@address@/ is owned by the caller.
-- 
-- /@vector@/ must point to an array of t'GI.Gio.Structs.InputVector.InputVector' structs and
-- /@numVectors@/ must be the length of this array.  These structs
-- describe the buffers that received data will be scattered into.
-- If /@numVectors@/ is -1, then /@vectors@/ is assumed to be terminated
-- by a t'GI.Gio.Structs.InputVector.InputVector' with a 'P.Nothing' buffer pointer.
-- 
-- As a special case, if /@numVectors@/ is 0 (in which case, /@vectors@/
-- may of course be 'P.Nothing'), then a single byte is received and
-- discarded. This is to facilitate the common practice of sending a
-- single \'\\0\' byte for the purposes of transferring ancillary data.
-- 
-- /@messages@/, if non-'P.Nothing', will be set to point to a newly-allocated
-- array of t'GI.Gio.Objects.SocketControlMessage.SocketControlMessage' instances or 'P.Nothing' if no such
-- messages was received. These correspond to the control messages
-- received from the kernel, one t'GI.Gio.Objects.SocketControlMessage.SocketControlMessage' per message
-- from the kernel. This array is 'P.Nothing'-terminated and must be freed
-- by the caller using 'GI.GLib.Functions.free' after calling 'GI.GObject.Objects.Object.objectUnref' on each
-- element. If /@messages@/ is 'P.Nothing', any control messages received will
-- be discarded.
-- 
-- /@numMessages@/, if non-'P.Nothing', will be set to the number of control
-- messages received.
-- 
-- If both /@messages@/ and /@numMessages@/ are non-'P.Nothing', then
-- /@numMessages@/ gives the number of t'GI.Gio.Objects.SocketControlMessage.SocketControlMessage' instances
-- in /@messages@/ (ie: not including the 'P.Nothing' terminator).
-- 
-- /@flags@/ is an in\/out parameter. The commonly available arguments
-- for this are available in the t'GI.Gio.Flags.SocketMsgFlags' enum, but the
-- values there are the same as the system values, and the flags
-- are passed in as-is, so you can pass in system-specific flags too
-- (and 'GI.Gio.Objects.Socket.socketReceiveMessage' may pass system-specific flags out).
-- Flags passed in to the parameter affect the receive operation; flags returned
-- out of it are relevant to the specific returned message.
-- 
-- As with 'GI.Gio.Objects.Socket.socketReceive', data may be discarded if /@socket@/ is
-- 'GI.Gio.Enums.SocketTypeDatagram' or 'GI.Gio.Enums.SocketTypeSeqpacket' and you do not
-- provide enough buffer space to read a complete message. You can pass
-- 'GI.Gio.Flags.SocketMsgFlagsPeek' in /@flags@/ to peek at the current message without
-- removing it from the receive queue, but there is no portable way to find
-- out the length of the message other than by reading it into a
-- sufficiently-large buffer.
-- 
-- If the socket is in blocking mode the call will block until there
-- is some data to receive, the connection is closed, or there is an
-- error. If there is no data available and the socket is in
-- non-blocking mode, a 'GI.Gio.Enums.IOErrorEnumWouldBlock' error will be
-- returned. To be notified when data is available, wait for the
-- 'GI.GObject.Flags.IOConditionIn' condition.
-- 
-- On error -1 is returned and /@error@/ is set accordingly.
-- 
-- /Since: 2.22/
socketReceiveMessage ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'
    -> [Gio.InputVector.InputVector]
    -- ^ /@vectors@/: an array of t'GI.Gio.Structs.InputVector.InputVector' structs
    -> Int32
    -- ^ /@flags@/: a pointer to an int containing t'GI.Gio.Flags.SocketMsgFlags' flags,
    --    which may additionally contain
    --    <http://man7.org/linux/man-pages/man2/recv.2.html other platform specific flags>
    -> Maybe (b)
    -- ^ /@cancellable@/: a @/GCancellable/@ or 'P.Nothing'
    -> m ((DI.Int64, Maybe Gio.SocketAddress.SocketAddress, Maybe [Gio.SocketControlMessage.SocketControlMessage], Int32))
    -- ^ __Returns:__ Number of bytes read, or 0 if the connection was closed by
    -- the peer, or -1 on error /(Can throw 'Data.GI.Base.GError.GError')/
socketReceiveMessage :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSocket a, IsCancellable b) =>
a
-> [InputVector]
-> Int32
-> Maybe b
-> m (Int64, Maybe SocketAddress, Maybe [SocketControlMessage],
      Int32)
socketReceiveMessage a
socket [InputVector]
vectors Int32
flags Maybe b
cancellable = IO
  (Int64, Maybe SocketAddress, Maybe [SocketControlMessage], Int32)
-> m (Int64, Maybe SocketAddress, Maybe [SocketControlMessage],
      Int32)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO
   (Int64, Maybe SocketAddress, Maybe [SocketControlMessage], Int32)
 -> m (Int64, Maybe SocketAddress, Maybe [SocketControlMessage],
       Int32))
-> IO
     (Int64, Maybe SocketAddress, Maybe [SocketControlMessage], Int32)
-> m (Int64, Maybe SocketAddress, Maybe [SocketControlMessage],
      Int32)
forall a b. (a -> b) -> a -> b
$ do
    let numVectors :: Int32
numVectors = Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> Int -> Int32
forall a b. (a -> b) -> a -> b
$ [InputVector] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [InputVector]
vectors
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    address <- callocMem :: IO (Ptr (Ptr Gio.SocketAddress.SocketAddress))
    vectors' <- mapM unsafeManagedPtrGetPtr vectors
    vectors'' <- packBlockArray 16 vectors'
    messages <- callocMem :: IO (Ptr (Ptr (Ptr Gio.SocketControlMessage.SocketControlMessage)))
    numMessages <- allocMem :: IO (Ptr Int32)
    flags' <- allocMem :: IO (Ptr Int32)
    poke flags' flags
    maybeCancellable <- case cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just b
jCancellable -> do
            jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_socket_receive_message socket' address vectors'' numVectors messages numMessages flags' maybeCancellable
        numMessages' <- peek numMessages
        address' <- peek address
        maybeAddress' <- convertIfNonNull address' $ \Ptr SocketAddress
address'' -> do
            address''' <- ((ManagedPtr SocketAddress -> SocketAddress)
-> Ptr SocketAddress -> IO SocketAddress
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr SocketAddress -> SocketAddress
Gio.SocketAddress.SocketAddress) Ptr SocketAddress
address''
            return address'''
        messages' <- peek messages
        maybeMessages' <- convertIfNonNull messages' $ \Ptr (Ptr SocketControlMessage)
messages'' -> do
            messages''' <- (Int32
-> Ptr (Ptr SocketControlMessage) -> IO [Ptr SocketControlMessage]
forall a b. Integral a => a -> Ptr (Ptr b) -> IO [Ptr b]
unpackPtrArrayWithLength Int32
numMessages') Ptr (Ptr SocketControlMessage)
messages''
            messages'''' <- mapM (wrapObject Gio.SocketControlMessage.SocketControlMessage) messages'''
            freeMem messages''
            return messages''''
        flags'' <- peek flags'
        touchManagedPtr socket
        mapM_ touchManagedPtr vectors
        whenJust cancellable touchManagedPtr
        freeMem address
        freeMem vectors''
        freeMem messages
        freeMem numMessages
        freeMem flags'
        return (result, maybeAddress', maybeMessages', flags'')
     ) (do
        freeMem address
        freeMem vectors''
        freeMem messages
        freeMem numMessages
        freeMem flags'
     )

#if defined(ENABLE_OVERLOADING)
data SocketReceiveMessageMethodInfo
instance (signature ~ ([Gio.InputVector.InputVector] -> Int32 -> Maybe (b) -> m ((DI.Int64, Maybe Gio.SocketAddress.SocketAddress, Maybe [Gio.SocketControlMessage.SocketControlMessage], Int32))), MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod SocketReceiveMessageMethodInfo a signature where
    overloadedMethod = socketReceiveMessage

instance O.OverloadedMethodInfo SocketReceiveMessageMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketReceiveMessage",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketReceiveMessage"
        })


#endif

-- method Socket::receive_messages
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "messages"
--           , argType =
--               TCArray
--                 False
--                 (-1)
--                 2
--                 (TInterface Name { namespace = "Gio" , name = "InputMessage" })
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an array of #GInputMessage structs"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "num_messages"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of elements in @messages"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "an int containing #GSocketMsgFlags flags for the overall operation,\n   which may additionally contain\n   [other platform specific flags](http://man7.org/linux/man-pages/man2/recv.2.html)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a %GCancellable or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "num_messages"
--              , argType = TBasicType TUInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "the number of elements in @messages"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , argCallbackUserData = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just (TBasicType TInt)
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_receive_messages" g_socket_receive_messages :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Ptr Gio.InputMessage.InputMessage ->    -- messages : TCArray False (-1) 2 (TInterface (Name {namespace = "Gio", name = "InputMessage"}))
    Word32 ->                               -- num_messages : TBasicType TUInt
    Int32 ->                                -- flags : TBasicType TInt
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO Int32

-- | Receive multiple data messages from /@socket@/ in one go.  This is the most
-- complicated and fully-featured version of this call. For easier use, see
-- 'GI.Gio.Objects.Socket.socketReceive', 'GI.Gio.Objects.Socket.socketReceiveFrom', and 'GI.Gio.Objects.Socket.socketReceiveMessage'.
-- 
-- /@messages@/ must point to an array of t'GI.Gio.Structs.InputMessage.InputMessage' structs and
-- /@numMessages@/ must be the length of this array. Each t'GI.Gio.Structs.InputMessage.InputMessage'
-- contains a pointer to an array of t'GI.Gio.Structs.InputVector.InputVector' structs describing the
-- buffers that the data received in each message will be written to. Using
-- multiple @/GInputVectors/@ is more memory-efficient than manually copying data
-- out of a single buffer to multiple sources, and more system-call-efficient
-- than making multiple calls to 'GI.Gio.Objects.Socket.socketReceive', such as in scenarios where
-- a lot of data packets need to be received (e.g. high-bandwidth video
-- streaming over RTP\/UDP).
-- 
-- /@flags@/ modify how all messages are received. The commonly available
-- arguments for this are available in the t'GI.Gio.Flags.SocketMsgFlags' enum, but the
-- values there are the same as the system values, and the flags
-- are passed in as-is, so you can pass in system-specific flags too. These
-- flags affect the overall receive operation. Flags affecting individual
-- messages are returned in t'GI.Gio.Structs.InputMessage.InputMessage'.@/flags/@.
-- 
-- The other members of t'GI.Gio.Structs.InputMessage.InputMessage' are treated as described in its
-- documentation.
-- 
-- If [Socket:blocking]("GI.Gio.Objects.Socket#g:attr:blocking") is 'P.True' the call will block until /@numMessages@/ have
-- been received, or the end of the stream is reached.
-- 
-- If [Socket:blocking]("GI.Gio.Objects.Socket#g:attr:blocking") is 'P.False' the call will return up to /@numMessages@/
-- without blocking, or 'GI.Gio.Enums.IOErrorEnumWouldBlock' if no messages are queued in the
-- operating system to be received.
-- 
-- In blocking mode, if [Socket:timeout]("GI.Gio.Objects.Socket#g:attr:timeout") is positive and is reached before any
-- messages are received, 'GI.Gio.Enums.IOErrorEnumTimedOut' is returned, otherwise up to
-- /@numMessages@/ are returned. (Note: This is effectively the
-- behaviour of @MSG_WAITFORONE@ with @/recvmmsg()/@.)
-- 
-- To be notified when messages are available, wait for the
-- 'GI.GObject.Flags.IOConditionIn' condition. Note though that you may still receive
-- 'GI.Gio.Enums.IOErrorEnumWouldBlock' from 'GI.Gio.Objects.Socket.socketReceiveMessages' even if you were
-- previously notified of a 'GI.GObject.Flags.IOConditionIn' condition.
-- 
-- If the remote peer closes the connection, any messages queued in the
-- operating system will be returned, and subsequent calls to
-- 'GI.Gio.Objects.Socket.socketReceiveMessages' will return 0 (with no error set).
-- 
-- On error -1 is returned and /@error@/ is set accordingly. An error will only
-- be returned if zero messages could be received; otherwise the number of
-- messages successfully received before the error will be returned.
-- 
-- /Since: 2.48/
socketReceiveMessages ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'
    -> [Gio.InputMessage.InputMessage]
    -- ^ /@messages@/: an array of t'GI.Gio.Structs.InputMessage.InputMessage' structs
    -> Int32
    -- ^ /@flags@/: an int containing t'GI.Gio.Flags.SocketMsgFlags' flags for the overall operation,
    --    which may additionally contain
    --    <http://man7.org/linux/man-pages/man2/recv.2.html other platform specific flags>
    -> Maybe (b)
    -- ^ /@cancellable@/: a @/GCancellable/@ or 'P.Nothing'
    -> m Int32
    -- ^ __Returns:__ number of messages received, or -1 on error. Note that the number
    --     of messages received may be smaller than /@numMessages@/ if in non-blocking
    --     mode, if the peer closed the connection, or if /@numMessages@/
    --     was larger than @UIO_MAXIOV@ (1024), in which case the caller may re-try
    --     to receive the remaining messages. /(Can throw 'Data.GI.Base.GError.GError')/
socketReceiveMessages :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSocket a, IsCancellable b) =>
a -> [InputMessage] -> Int32 -> Maybe b -> m Int32
socketReceiveMessages a
socket [InputMessage]
messages Int32
flags Maybe b
cancellable = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    let numMessages :: Word32
numMessages = Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word32) -> Int -> Word32
forall a b. (a -> b) -> a -> b
$ [InputMessage] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [InputMessage]
messages
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    messages' <- mapM unsafeManagedPtrGetPtr messages
    messages'' <- packBlockArray 56 messages'
    maybeCancellable <- case cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just b
jCancellable -> do
            jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_socket_receive_messages socket' messages'' numMessages flags maybeCancellable
        touchManagedPtr socket
        mapM_ touchManagedPtr messages
        whenJust cancellable touchManagedPtr
        freeMem messages''
        return result
     ) (do
        freeMem messages''
     )

#if defined(ENABLE_OVERLOADING)
data SocketReceiveMessagesMethodInfo
instance (signature ~ ([Gio.InputMessage.InputMessage] -> Int32 -> Maybe (b) -> m Int32), MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod SocketReceiveMessagesMethodInfo a signature where
    overloadedMethod = socketReceiveMessages

instance O.OverloadedMethodInfo SocketReceiveMessagesMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketReceiveMessages",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketReceiveMessages"
        })


#endif

-- method Socket::receive_with_blocking
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "buffer"
--           , argType = TCArray False (-1) 2 (TBasicType TUInt8)
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "\n    a buffer to read data into (which should be at least @size bytes long)."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TSize
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the number of bytes you want to read from the socket"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "blocking"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether to do blocking or non-blocking I/O"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a %GCancellable or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "size"
--              , argType = TBasicType TSize
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just "the number of bytes you want to read from the socket"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , argCallbackUserData = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just (TBasicType TSSize)
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_receive_with_blocking" g_socket_receive_with_blocking :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Ptr Word8 ->                            -- buffer : TCArray False (-1) 2 (TBasicType TUInt8)
    FCT.CSize ->                            -- size : TBasicType TSize
    CInt ->                                 -- blocking : TBasicType TBoolean
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO DI.Int64

-- | This behaves exactly the same as 'GI.Gio.Objects.Socket.socketReceive', except that
-- the choice of blocking or non-blocking behavior is determined by
-- the /@blocking@/ argument rather than by /@socket@/\'s properties.
-- 
-- /Since: 2.26/
socketReceiveWithBlocking ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'
    -> ByteString
    -- ^ /@buffer@/: 
    --     a buffer to read data into (which should be at least /@size@/ bytes long).
    -> Bool
    -- ^ /@blocking@/: whether to do blocking or non-blocking I\/O
    -> Maybe (b)
    -- ^ /@cancellable@/: a @/GCancellable/@ or 'P.Nothing'
    -> m ((DI.Int64, ByteString))
    -- ^ __Returns:__ Number of bytes read, or 0 if the connection was closed by
    -- the peer, or -1 on error /(Can throw 'Data.GI.Base.GError.GError')/
socketReceiveWithBlocking :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSocket a, IsCancellable b) =>
a -> ByteString -> Bool -> Maybe b -> m (Int64, ByteString)
socketReceiveWithBlocking a
socket ByteString
buffer Bool
blocking Maybe b
cancellable = IO (Int64, ByteString) -> m (Int64, ByteString)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int64, ByteString) -> m (Int64, ByteString))
-> IO (Int64, ByteString) -> m (Int64, ByteString)
forall a b. (a -> b) -> a -> b
$ do
    let size :: CSize
size = Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CSize) -> Int -> CSize
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
buffer
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    buffer' <- packByteString buffer
    let blocking' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
blocking
    maybeCancellable <- case cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just b
jCancellable -> do
            jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_socket_receive_with_blocking socket' buffer' size blocking' maybeCancellable
        buffer'' <- (unpackByteStringWithLength size) buffer'
        freeMem buffer'
        touchManagedPtr socket
        whenJust cancellable touchManagedPtr
        return (result, buffer'')
     ) (do
        freeMem buffer'
     )

#if defined(ENABLE_OVERLOADING)
data SocketReceiveWithBlockingMethodInfo
instance (signature ~ (ByteString -> Bool -> Maybe (b) -> m ((DI.Int64, ByteString))), MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod SocketReceiveWithBlockingMethodInfo a signature where
    overloadedMethod = socketReceiveWithBlocking

instance O.OverloadedMethodInfo SocketReceiveWithBlockingMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketReceiveWithBlocking",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketReceiveWithBlocking"
        })


#endif

-- method Socket::send
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "buffer"
--           , argType = TCArray False (-1) 2 (TBasicType TUInt8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the buffer\n    containing the data to send."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TSize
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of bytes to send"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a %GCancellable or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "size"
--              , argType = TBasicType TSize
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "the number of bytes to send"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , argCallbackUserData = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just (TBasicType TSSize)
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_send" g_socket_send :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Ptr Word8 ->                            -- buffer : TCArray False (-1) 2 (TBasicType TUInt8)
    FCT.CSize ->                            -- size : TBasicType TSize
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO DI.Int64

-- | Tries to send /@size@/ bytes from /@buffer@/ on the socket. This is
-- mainly used by connection-oriented sockets; it is identical to
-- 'GI.Gio.Objects.Socket.socketSendTo' with /@address@/ set to 'P.Nothing'.
-- 
-- If the socket is in blocking mode the call will block until there is
-- space for the data in the socket queue. If there is no space available
-- and the socket is in non-blocking mode a 'GI.Gio.Enums.IOErrorEnumWouldBlock' error
-- will be returned. To be notified when space is available, wait for the
-- 'GI.GObject.Flags.IOConditionOut' condition. Note though that you may still receive
-- 'GI.Gio.Enums.IOErrorEnumWouldBlock' from 'GI.Gio.Objects.Socket.socketSend' even if you were previously
-- notified of a 'GI.GObject.Flags.IOConditionOut' condition. (On Windows in particular, this is
-- very common due to the way the underlying APIs work.)
-- 
-- On error -1 is returned and /@error@/ is set accordingly.
-- 
-- /Since: 2.22/
socketSend ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'
    -> ByteString
    -- ^ /@buffer@/: the buffer
    --     containing the data to send.
    -> Maybe (b)
    -- ^ /@cancellable@/: a @/GCancellable/@ or 'P.Nothing'
    -> m DI.Int64
    -- ^ __Returns:__ Number of bytes written (which may be less than /@size@/), or -1
    -- on error /(Can throw 'Data.GI.Base.GError.GError')/
socketSend :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSocket a, IsCancellable b) =>
a -> ByteString -> Maybe b -> m Int64
socketSend a
socket ByteString
buffer Maybe b
cancellable = IO Int64 -> m Int64
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int64 -> m Int64) -> IO Int64 -> m Int64
forall a b. (a -> b) -> a -> b
$ do
    let size :: CSize
size = Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CSize) -> Int -> CSize
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
buffer
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    buffer' <- packByteString buffer
    maybeCancellable <- case cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just b
jCancellable -> do
            jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_socket_send socket' buffer' size maybeCancellable
        touchManagedPtr socket
        whenJust cancellable touchManagedPtr
        freeMem buffer'
        return result
     ) (do
        freeMem buffer'
     )

#if defined(ENABLE_OVERLOADING)
data SocketSendMethodInfo
instance (signature ~ (ByteString -> Maybe (b) -> m DI.Int64), MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod SocketSendMethodInfo a signature where
    overloadedMethod = socketSend

instance O.OverloadedMethodInfo SocketSendMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketSend",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketSend"
        })


#endif

-- method Socket::send_message
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "address"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SocketAddress" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocketAddress, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "vectors"
--           , argType =
--               TCArray
--                 False
--                 (-1)
--                 3
--                 (TInterface Name { namespace = "Gio" , name = "OutputVector" })
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an array of #GOutputVector structs"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "num_vectors"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of elements in @vectors, or -1"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "messages"
--           , argType =
--               TCArray
--                 False
--                 (-1)
--                 5
--                 (TInterface
--                    Name { namespace = "Gio" , name = "SocketControlMessage" })
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a pointer to an\n  array of #GSocketControlMessages, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "num_messages"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of elements in @messages, or -1."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "an int containing #GSocketMsgFlags flags, which may additionally\n   contain [other platform specific flags](http://man7.org/linux/man-pages/man2/recv.2.html)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a %GCancellable or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "num_messages"
--              , argType = TBasicType TInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "number of elements in @messages, or -1."
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , argCallbackUserData = False
--              , transfer = TransferNothing
--              }
--          , Arg
--              { argCName = "num_vectors"
--              , argType = TBasicType TInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "the number of elements in @vectors, or -1"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , argCallbackUserData = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just (TBasicType TSSize)
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_send_message" g_socket_send_message :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Ptr Gio.SocketAddress.SocketAddress ->  -- address : TInterface (Name {namespace = "Gio", name = "SocketAddress"})
    Ptr Gio.OutputVector.OutputVector ->    -- vectors : TCArray False (-1) 3 (TInterface (Name {namespace = "Gio", name = "OutputVector"}))
    Int32 ->                                -- num_vectors : TBasicType TInt
    Ptr (Ptr Gio.SocketControlMessage.SocketControlMessage) -> -- messages : TCArray False (-1) 5 (TInterface (Name {namespace = "Gio", name = "SocketControlMessage"}))
    Int32 ->                                -- num_messages : TBasicType TInt
    Int32 ->                                -- flags : TBasicType TInt
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO DI.Int64

-- | Send data to /@address@/ on /@socket@/.  For sending multiple messages see
-- 'GI.Gio.Objects.Socket.socketSendMessages'; for easier use, see
-- 'GI.Gio.Objects.Socket.socketSend' and 'GI.Gio.Objects.Socket.socketSendTo'.
-- 
-- If /@address@/ is 'P.Nothing' then the message is sent to the default receiver
-- (set by 'GI.Gio.Objects.Socket.socketConnect').
-- 
-- /@vectors@/ must point to an array of t'GI.Gio.Structs.OutputVector.OutputVector' structs and
-- /@numVectors@/ must be the length of this array. (If /@numVectors@/ is -1,
-- then /@vectors@/ is assumed to be terminated by a t'GI.Gio.Structs.OutputVector.OutputVector' with a
-- 'P.Nothing' buffer pointer.) The t'GI.Gio.Structs.OutputVector.OutputVector' structs describe the buffers
-- that the sent data will be gathered from. Using multiple
-- @/GOutputVectors/@ is more memory-efficient than manually copying
-- data from multiple sources into a single buffer, and more
-- network-efficient than making multiple calls to 'GI.Gio.Objects.Socket.socketSend'.
-- 
-- /@messages@/, if non-'P.Nothing', is taken to point to an array of /@numMessages@/
-- t'GI.Gio.Objects.SocketControlMessage.SocketControlMessage' instances. These correspond to the control
-- messages to be sent on the socket.
-- If /@numMessages@/ is -1 then /@messages@/ is treated as a 'P.Nothing'-terminated
-- array.
-- 
-- /@flags@/ modify how the message is sent. The commonly available arguments
-- for this are available in the t'GI.Gio.Flags.SocketMsgFlags' enum, but the
-- values there are the same as the system values, and the flags
-- are passed in as-is, so you can pass in system-specific flags too.
-- 
-- If the socket is in blocking mode the call will block until there is
-- space for the data in the socket queue. If there is no space available
-- and the socket is in non-blocking mode a 'GI.Gio.Enums.IOErrorEnumWouldBlock' error
-- will be returned. To be notified when space is available, wait for the
-- 'GI.GObject.Flags.IOConditionOut' condition. Note though that you may still receive
-- 'GI.Gio.Enums.IOErrorEnumWouldBlock' from 'GI.Gio.Objects.Socket.socketSend' even if you were previously
-- notified of a 'GI.GObject.Flags.IOConditionOut' condition. (On Windows in particular, this is
-- very common due to the way the underlying APIs work.)
-- 
-- The sum of the sizes of each t'GI.Gio.Structs.OutputVector.OutputVector' in vectors must not be
-- greater than @/G_MAXSSIZE/@. If the message can be larger than this,
-- then it is mandatory to use the 'GI.Gio.Objects.Socket.socketSendMessageWithTimeout'
-- function.
-- 
-- On error -1 is returned and /@error@/ is set accordingly.
-- 
-- /Since: 2.22/
socketSendMessage ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.SocketAddress.IsSocketAddress b, Gio.Cancellable.IsCancellable c) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'
    -> Maybe (b)
    -- ^ /@address@/: a t'GI.Gio.Objects.SocketAddress.SocketAddress', or 'P.Nothing'
    -> [Gio.OutputVector.OutputVector]
    -- ^ /@vectors@/: an array of t'GI.Gio.Structs.OutputVector.OutputVector' structs
    -> Maybe ([Gio.SocketControlMessage.SocketControlMessage])
    -- ^ /@messages@/: a pointer to an
    --   array of @/GSocketControlMessages/@, or 'P.Nothing'.
    -> Int32
    -- ^ /@flags@/: an int containing t'GI.Gio.Flags.SocketMsgFlags' flags, which may additionally
    --    contain <http://man7.org/linux/man-pages/man2/recv.2.html other platform specific flags>
    -> Maybe (c)
    -- ^ /@cancellable@/: a @/GCancellable/@ or 'P.Nothing'
    -> m DI.Int64
    -- ^ __Returns:__ Number of bytes written (which may be less than /@size@/), or -1
    -- on error /(Can throw 'Data.GI.Base.GError.GError')/
socketSendMessage :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsSocket a, IsSocketAddress b,
 IsCancellable c) =>
a
-> Maybe b
-> [OutputVector]
-> Maybe [SocketControlMessage]
-> Int32
-> Maybe c
-> m Int64
socketSendMessage a
socket Maybe b
address [OutputVector]
vectors Maybe [SocketControlMessage]
messages Int32
flags Maybe c
cancellable = IO Int64 -> m Int64
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int64 -> m Int64) -> IO Int64 -> m Int64
forall a b. (a -> b) -> a -> b
$ do
    let numMessages :: Int32
numMessages = case Maybe [SocketControlMessage]
messages of
            Maybe [SocketControlMessage]
Nothing -> Int32
0
            Just [SocketControlMessage]
jMessages -> Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> Int -> Int32
forall a b. (a -> b) -> a -> b
$ [SocketControlMessage] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [SocketControlMessage]
jMessages
    let numVectors :: Int32
numVectors = Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> Int -> Int32
forall a b. (a -> b) -> a -> b
$ [OutputVector] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [OutputVector]
vectors
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    maybeAddress <- case address of
        Maybe b
Nothing -> Ptr SocketAddress -> IO (Ptr SocketAddress)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr SocketAddress
forall a. Ptr a
FP.nullPtr
        Just b
jAddress -> do
            jAddress' <- b -> IO (Ptr SocketAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jAddress
            return jAddress'
    vectors' <- mapM unsafeManagedPtrGetPtr vectors
    vectors'' <- packBlockArray 16 vectors'
    maybeMessages <- case messages of
        Maybe [SocketControlMessage]
Nothing -> Ptr (Ptr SocketControlMessage)
-> IO (Ptr (Ptr SocketControlMessage))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr (Ptr SocketControlMessage)
forall a. Ptr a
FP.nullPtr
        Just [SocketControlMessage]
jMessages -> do
            jMessages' <- (SocketControlMessage -> IO (Ptr SocketControlMessage))
-> [SocketControlMessage] -> IO [Ptr SocketControlMessage]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM SocketControlMessage -> IO (Ptr SocketControlMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr [SocketControlMessage]
jMessages
            jMessages'' <- packPtrArray jMessages'
            return jMessages''
    maybeCancellable <- case cancellable of
        Maybe c
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just c
jCancellable -> do
            jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_socket_send_message socket' maybeAddress vectors'' numVectors maybeMessages numMessages flags maybeCancellable
        touchManagedPtr socket
        whenJust address touchManagedPtr
        mapM_ touchManagedPtr vectors
        whenJust messages (mapM_ touchManagedPtr)
        whenJust cancellable touchManagedPtr
        freeMem vectors''
        freeMem maybeMessages
        return result
     ) (do
        freeMem vectors''
        freeMem maybeMessages
     )

#if defined(ENABLE_OVERLOADING)
data SocketSendMessageMethodInfo
instance (signature ~ (Maybe (b) -> [Gio.OutputVector.OutputVector] -> Maybe ([Gio.SocketControlMessage.SocketControlMessage]) -> Int32 -> Maybe (c) -> m DI.Int64), MonadIO m, IsSocket a, Gio.SocketAddress.IsSocketAddress b, Gio.Cancellable.IsCancellable c) => O.OverloadedMethod SocketSendMessageMethodInfo a signature where
    overloadedMethod = socketSendMessage

instance O.OverloadedMethodInfo SocketSendMessageMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketSendMessage",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketSendMessage"
        })


#endif

-- method Socket::send_message_with_timeout
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "address"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SocketAddress" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocketAddress, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "vectors"
--           , argType =
--               TCArray
--                 False
--                 (-1)
--                 3
--                 (TInterface Name { namespace = "Gio" , name = "OutputVector" })
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an array of #GOutputVector structs"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "num_vectors"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of elements in @vectors, or -1"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "messages"
--           , argType =
--               TCArray
--                 False
--                 (-1)
--                 5
--                 (TInterface
--                    Name { namespace = "Gio" , name = "SocketControlMessage" })
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a pointer to an\n  array of #GSocketControlMessages, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "num_messages"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of elements in @messages, or -1."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "an int containing #GSocketMsgFlags flags, which may additionally\n   contain [other platform specific flags](http://man7.org/linux/man-pages/man2/recv.2.html)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "timeout_us"
--           , argType = TBasicType TInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the maximum time (in microseconds) to wait, or -1"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "bytes_written"
--           , argType = TBasicType TSize
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "location to store the number of bytes that were written to the socket"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a %GCancellable or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "num_messages"
--              , argType = TBasicType TInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "number of elements in @messages, or -1."
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , argCallbackUserData = False
--              , transfer = TransferNothing
--              }
--          , Arg
--              { argCName = "num_vectors"
--              , argType = TBasicType TInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "the number of elements in @vectors, or -1"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , argCallbackUserData = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "PollableReturn" })
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_send_message_with_timeout" g_socket_send_message_with_timeout :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Ptr Gio.SocketAddress.SocketAddress ->  -- address : TInterface (Name {namespace = "Gio", name = "SocketAddress"})
    Ptr Gio.OutputVector.OutputVector ->    -- vectors : TCArray False (-1) 3 (TInterface (Name {namespace = "Gio", name = "OutputVector"}))
    Int32 ->                                -- num_vectors : TBasicType TInt
    Ptr (Ptr Gio.SocketControlMessage.SocketControlMessage) -> -- messages : TCArray False (-1) 5 (TInterface (Name {namespace = "Gio", name = "SocketControlMessage"}))
    Int32 ->                                -- num_messages : TBasicType TInt
    Int32 ->                                -- flags : TBasicType TInt
    Int64 ->                                -- timeout_us : TBasicType TInt64
    Ptr FCT.CSize ->                        -- bytes_written : TBasicType TSize
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | This behaves exactly the same as 'GI.Gio.Objects.Socket.socketSendMessage', except that
-- the choice of timeout behavior is determined by the /@timeoutUs@/ argument
-- rather than by /@socket@/\'s properties.
-- 
-- On error 'GI.Gio.Enums.PollableReturnFailed' is returned and /@error@/ is set accordingly, or
-- if the socket is currently not writable 'GI.Gio.Enums.PollableReturnWouldBlock' is
-- returned. /@bytesWritten@/ will contain 0 in both cases.
-- 
-- /Since: 2.60/
socketSendMessageWithTimeout ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.SocketAddress.IsSocketAddress b, Gio.Cancellable.IsCancellable c) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'
    -> Maybe (b)
    -- ^ /@address@/: a t'GI.Gio.Objects.SocketAddress.SocketAddress', or 'P.Nothing'
    -> [Gio.OutputVector.OutputVector]
    -- ^ /@vectors@/: an array of t'GI.Gio.Structs.OutputVector.OutputVector' structs
    -> Maybe ([Gio.SocketControlMessage.SocketControlMessage])
    -- ^ /@messages@/: a pointer to an
    --   array of @/GSocketControlMessages/@, or 'P.Nothing'.
    -> Int32
    -- ^ /@flags@/: an int containing t'GI.Gio.Flags.SocketMsgFlags' flags, which may additionally
    --    contain <http://man7.org/linux/man-pages/man2/recv.2.html other platform specific flags>
    -> Int64
    -- ^ /@timeoutUs@/: the maximum time (in microseconds) to wait, or -1
    -> Maybe (c)
    -- ^ /@cancellable@/: a @/GCancellable/@ or 'P.Nothing'
    -> m ((Gio.Enums.PollableReturn, FCT.CSize))
    -- ^ __Returns:__ 'GI.Gio.Enums.PollableReturnOk' if all data was successfully written,
    -- 'GI.Gio.Enums.PollableReturnWouldBlock' if the socket is currently not writable, or
    -- 'GI.Gio.Enums.PollableReturnFailed' if an error happened and /@error@/ is set. /(Can throw 'Data.GI.Base.GError.GError')/
socketSendMessageWithTimeout :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsSocket a, IsSocketAddress b,
 IsCancellable c) =>
a
-> Maybe b
-> [OutputVector]
-> Maybe [SocketControlMessage]
-> Int32
-> Int64
-> Maybe c
-> m (PollableReturn, CSize)
socketSendMessageWithTimeout a
socket Maybe b
address [OutputVector]
vectors Maybe [SocketControlMessage]
messages Int32
flags Int64
timeoutUs Maybe c
cancellable = IO (PollableReturn, CSize) -> m (PollableReturn, CSize)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (PollableReturn, CSize) -> m (PollableReturn, CSize))
-> IO (PollableReturn, CSize) -> m (PollableReturn, CSize)
forall a b. (a -> b) -> a -> b
$ do
    let numMessages :: Int32
numMessages = case Maybe [SocketControlMessage]
messages of
            Maybe [SocketControlMessage]
Nothing -> Int32
0
            Just [SocketControlMessage]
jMessages -> Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> Int -> Int32
forall a b. (a -> b) -> a -> b
$ [SocketControlMessage] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [SocketControlMessage]
jMessages
    let numVectors :: Int32
numVectors = Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> Int -> Int32
forall a b. (a -> b) -> a -> b
$ [OutputVector] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [OutputVector]
vectors
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    maybeAddress <- case address of
        Maybe b
Nothing -> Ptr SocketAddress -> IO (Ptr SocketAddress)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr SocketAddress
forall a. Ptr a
FP.nullPtr
        Just b
jAddress -> do
            jAddress' <- b -> IO (Ptr SocketAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jAddress
            return jAddress'
    vectors' <- mapM unsafeManagedPtrGetPtr vectors
    vectors'' <- packBlockArray 16 vectors'
    maybeMessages <- case messages of
        Maybe [SocketControlMessage]
Nothing -> Ptr (Ptr SocketControlMessage)
-> IO (Ptr (Ptr SocketControlMessage))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr (Ptr SocketControlMessage)
forall a. Ptr a
FP.nullPtr
        Just [SocketControlMessage]
jMessages -> do
            jMessages' <- (SocketControlMessage -> IO (Ptr SocketControlMessage))
-> [SocketControlMessage] -> IO [Ptr SocketControlMessage]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM SocketControlMessage -> IO (Ptr SocketControlMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr [SocketControlMessage]
jMessages
            jMessages'' <- packPtrArray jMessages'
            return jMessages''
    bytesWritten <- allocMem :: IO (Ptr FCT.CSize)
    maybeCancellable <- case cancellable of
        Maybe c
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just c
jCancellable -> do
            jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_socket_send_message_with_timeout socket' maybeAddress vectors'' numVectors maybeMessages numMessages flags timeoutUs bytesWritten maybeCancellable
        let result' = (Int -> PollableReturn
forall a. Enum a => Int -> a
toEnum (Int -> PollableReturn) -> (CInt -> Int) -> CInt -> PollableReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CInt
result
        bytesWritten' <- peek bytesWritten
        touchManagedPtr socket
        whenJust address touchManagedPtr
        mapM_ touchManagedPtr vectors
        whenJust messages (mapM_ touchManagedPtr)
        whenJust cancellable touchManagedPtr
        freeMem vectors''
        freeMem maybeMessages
        freeMem bytesWritten
        return (result', bytesWritten')
     ) (do
        freeMem vectors''
        freeMem maybeMessages
        freeMem bytesWritten
     )

#if defined(ENABLE_OVERLOADING)
data SocketSendMessageWithTimeoutMethodInfo
instance (signature ~ (Maybe (b) -> [Gio.OutputVector.OutputVector] -> Maybe ([Gio.SocketControlMessage.SocketControlMessage]) -> Int32 -> Int64 -> Maybe (c) -> m ((Gio.Enums.PollableReturn, FCT.CSize))), MonadIO m, IsSocket a, Gio.SocketAddress.IsSocketAddress b, Gio.Cancellable.IsCancellable c) => O.OverloadedMethod SocketSendMessageWithTimeoutMethodInfo a signature where
    overloadedMethod = socketSendMessageWithTimeout

instance O.OverloadedMethodInfo SocketSendMessageWithTimeoutMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketSendMessageWithTimeout",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketSendMessageWithTimeout"
        })


#endif

-- method Socket::send_messages
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "messages"
--           , argType =
--               TCArray
--                 False
--                 (-1)
--                 2
--                 (TInterface Name { namespace = "Gio" , name = "OutputMessage" })
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an array of #GOutputMessage structs"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "num_messages"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of elements in @messages"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "an int containing #GSocketMsgFlags flags, which may additionally\n   contain [other platform specific flags](http://man7.org/linux/man-pages/man2/recv.2.html)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a %GCancellable or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "num_messages"
--              , argType = TBasicType TUInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "the number of elements in @messages"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , argCallbackUserData = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just (TBasicType TInt)
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_send_messages" g_socket_send_messages :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Ptr Gio.OutputMessage.OutputMessage ->  -- messages : TCArray False (-1) 2 (TInterface (Name {namespace = "Gio", name = "OutputMessage"}))
    Word32 ->                               -- num_messages : TBasicType TUInt
    Int32 ->                                -- flags : TBasicType TInt
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO Int32

-- | Send multiple data messages from /@socket@/ in one go.  This is the most
-- complicated and fully-featured version of this call. For easier use, see
-- 'GI.Gio.Objects.Socket.socketSend', 'GI.Gio.Objects.Socket.socketSendTo', and 'GI.Gio.Objects.Socket.socketSendMessage'.
-- 
-- /@messages@/ must point to an array of t'GI.Gio.Structs.OutputMessage.OutputMessage' structs and
-- /@numMessages@/ must be the length of this array. Each t'GI.Gio.Structs.OutputMessage.OutputMessage'
-- contains an address to send the data to, and a pointer to an array of
-- t'GI.Gio.Structs.OutputVector.OutputVector' structs to describe the buffers that the data to be sent
-- for each message will be gathered from. Using multiple @/GOutputVectors/@ is
-- more memory-efficient than manually copying data from multiple sources
-- into a single buffer, and more network-efficient than making multiple
-- calls to 'GI.Gio.Objects.Socket.socketSend'. Sending multiple messages in one go avoids the
-- overhead of making a lot of syscalls in scenarios where a lot of data
-- packets need to be sent (e.g. high-bandwidth video streaming over RTP\/UDP),
-- or where the same data needs to be sent to multiple recipients.
-- 
-- /@flags@/ modify how the message is sent. The commonly available arguments
-- for this are available in the t'GI.Gio.Flags.SocketMsgFlags' enum, but the
-- values there are the same as the system values, and the flags
-- are passed in as-is, so you can pass in system-specific flags too.
-- 
-- If the socket is in blocking mode the call will block until there is
-- space for all the data in the socket queue. If there is no space available
-- and the socket is in non-blocking mode a 'GI.Gio.Enums.IOErrorEnumWouldBlock' error
-- will be returned if no data was written at all, otherwise the number of
-- messages sent will be returned. To be notified when space is available,
-- wait for the 'GI.GObject.Flags.IOConditionOut' condition. Note though that you may still receive
-- 'GI.Gio.Enums.IOErrorEnumWouldBlock' from 'GI.Gio.Objects.Socket.socketSend' even if you were previously
-- notified of a 'GI.GObject.Flags.IOConditionOut' condition. (On Windows in particular, this is
-- very common due to the way the underlying APIs work.)
-- 
-- On error -1 is returned and /@error@/ is set accordingly. An error will only
-- be returned if zero messages could be sent; otherwise the number of messages
-- successfully sent before the error will be returned.
-- 
-- /Since: 2.44/
socketSendMessages ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'
    -> [Gio.OutputMessage.OutputMessage]
    -- ^ /@messages@/: an array of t'GI.Gio.Structs.OutputMessage.OutputMessage' structs
    -> Int32
    -- ^ /@flags@/: an int containing t'GI.Gio.Flags.SocketMsgFlags' flags, which may additionally
    --    contain <http://man7.org/linux/man-pages/man2/recv.2.html other platform specific flags>
    -> Maybe (b)
    -- ^ /@cancellable@/: a @/GCancellable/@ or 'P.Nothing'
    -> m Int32
    -- ^ __Returns:__ number of messages sent, or -1 on error. Note that the number of
    --     messages sent may be smaller than /@numMessages@/ if the socket is
    --     non-blocking or if /@numMessages@/ was larger than UIO_MAXIOV (1024),
    --     in which case the caller may re-try to send the remaining messages. /(Can throw 'Data.GI.Base.GError.GError')/
socketSendMessages :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSocket a, IsCancellable b) =>
a -> [OutputMessage] -> Int32 -> Maybe b -> m Int32
socketSendMessages a
socket [OutputMessage]
messages Int32
flags Maybe b
cancellable = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    let numMessages :: Word32
numMessages = Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word32) -> Int -> Word32
forall a b. (a -> b) -> a -> b
$ [OutputMessage] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [OutputMessage]
messages
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    messages' <- mapM unsafeManagedPtrGetPtr messages
    messages'' <- packBlockArray 40 messages'
    maybeCancellable <- case cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just b
jCancellable -> do
            jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_socket_send_messages socket' messages'' numMessages flags maybeCancellable
        touchManagedPtr socket
        mapM_ touchManagedPtr messages
        whenJust cancellable touchManagedPtr
        freeMem messages''
        return result
     ) (do
        freeMem messages''
     )

#if defined(ENABLE_OVERLOADING)
data SocketSendMessagesMethodInfo
instance (signature ~ ([Gio.OutputMessage.OutputMessage] -> Int32 -> Maybe (b) -> m Int32), MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod SocketSendMessagesMethodInfo a signature where
    overloadedMethod = socketSendMessages

instance O.OverloadedMethodInfo SocketSendMessagesMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketSendMessages",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketSendMessages"
        })


#endif

-- method Socket::send_to
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "address"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SocketAddress" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocketAddress, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "buffer"
--           , argType = TCArray False (-1) 3 (TBasicType TUInt8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the buffer\n    containing the data to send."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TSize
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of bytes to send"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a %GCancellable or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "size"
--              , argType = TBasicType TSize
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "the number of bytes to send"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , argCallbackUserData = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just (TBasicType TSSize)
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_send_to" g_socket_send_to :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Ptr Gio.SocketAddress.SocketAddress ->  -- address : TInterface (Name {namespace = "Gio", name = "SocketAddress"})
    Ptr Word8 ->                            -- buffer : TCArray False (-1) 3 (TBasicType TUInt8)
    FCT.CSize ->                            -- size : TBasicType TSize
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO DI.Int64

-- | Tries to send /@size@/ bytes from /@buffer@/ to /@address@/. If /@address@/ is
-- 'P.Nothing' then the message is sent to the default receiver (set by
-- 'GI.Gio.Objects.Socket.socketConnect').
-- 
-- See 'GI.Gio.Objects.Socket.socketSend' for additional information.
-- 
-- /Since: 2.22/
socketSendTo ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.SocketAddress.IsSocketAddress b, Gio.Cancellable.IsCancellable c) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'
    -> Maybe (b)
    -- ^ /@address@/: a t'GI.Gio.Objects.SocketAddress.SocketAddress', or 'P.Nothing'
    -> ByteString
    -- ^ /@buffer@/: the buffer
    --     containing the data to send.
    -> Maybe (c)
    -- ^ /@cancellable@/: a @/GCancellable/@ or 'P.Nothing'
    -> m DI.Int64
    -- ^ __Returns:__ Number of bytes written (which may be less than /@size@/), or -1
    -- on error /(Can throw 'Data.GI.Base.GError.GError')/
socketSendTo :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsSocket a, IsSocketAddress b,
 IsCancellable c) =>
a -> Maybe b -> ByteString -> Maybe c -> m Int64
socketSendTo a
socket Maybe b
address ByteString
buffer Maybe c
cancellable = IO Int64 -> m Int64
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int64 -> m Int64) -> IO Int64 -> m Int64
forall a b. (a -> b) -> a -> b
$ do
    let size :: CSize
size = Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CSize) -> Int -> CSize
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
buffer
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    maybeAddress <- case address of
        Maybe b
Nothing -> Ptr SocketAddress -> IO (Ptr SocketAddress)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr SocketAddress
forall a. Ptr a
FP.nullPtr
        Just b
jAddress -> do
            jAddress' <- b -> IO (Ptr SocketAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jAddress
            return jAddress'
    buffer' <- packByteString buffer
    maybeCancellable <- case cancellable of
        Maybe c
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just c
jCancellable -> do
            jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_socket_send_to socket' maybeAddress buffer' size maybeCancellable
        touchManagedPtr socket
        whenJust address touchManagedPtr
        whenJust cancellable touchManagedPtr
        freeMem buffer'
        return result
     ) (do
        freeMem buffer'
     )

#if defined(ENABLE_OVERLOADING)
data SocketSendToMethodInfo
instance (signature ~ (Maybe (b) -> ByteString -> Maybe (c) -> m DI.Int64), MonadIO m, IsSocket a, Gio.SocketAddress.IsSocketAddress b, Gio.Cancellable.IsCancellable c) => O.OverloadedMethod SocketSendToMethodInfo a signature where
    overloadedMethod = socketSendTo

instance O.OverloadedMethodInfo SocketSendToMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketSendTo",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketSendTo"
        })


#endif

-- method Socket::send_with_blocking
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "buffer"
--           , argType = TCArray False (-1) 2 (TBasicType TUInt8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the buffer\n    containing the data to send."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TSize
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of bytes to send"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "blocking"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether to do blocking or non-blocking I/O"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a %GCancellable or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "size"
--              , argType = TBasicType TSize
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "the number of bytes to send"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , argCallbackUserData = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just (TBasicType TSSize)
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_send_with_blocking" g_socket_send_with_blocking :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Ptr Word8 ->                            -- buffer : TCArray False (-1) 2 (TBasicType TUInt8)
    FCT.CSize ->                            -- size : TBasicType TSize
    CInt ->                                 -- blocking : TBasicType TBoolean
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO DI.Int64

-- | This behaves exactly the same as 'GI.Gio.Objects.Socket.socketSend', except that
-- the choice of blocking or non-blocking behavior is determined by
-- the /@blocking@/ argument rather than by /@socket@/\'s properties.
-- 
-- /Since: 2.26/
socketSendWithBlocking ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'
    -> ByteString
    -- ^ /@buffer@/: the buffer
    --     containing the data to send.
    -> Bool
    -- ^ /@blocking@/: whether to do blocking or non-blocking I\/O
    -> Maybe (b)
    -- ^ /@cancellable@/: a @/GCancellable/@ or 'P.Nothing'
    -> m DI.Int64
    -- ^ __Returns:__ Number of bytes written (which may be less than /@size@/), or -1
    -- on error /(Can throw 'Data.GI.Base.GError.GError')/
socketSendWithBlocking :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSocket a, IsCancellable b) =>
a -> ByteString -> Bool -> Maybe b -> m Int64
socketSendWithBlocking a
socket ByteString
buffer Bool
blocking Maybe b
cancellable = IO Int64 -> m Int64
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int64 -> m Int64) -> IO Int64 -> m Int64
forall a b. (a -> b) -> a -> b
$ do
    let size :: CSize
size = Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CSize) -> Int -> CSize
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
buffer
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    buffer' <- packByteString buffer
    let blocking' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
blocking
    maybeCancellable <- case cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just b
jCancellable -> do
            jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_socket_send_with_blocking socket' buffer' size blocking' maybeCancellable
        touchManagedPtr socket
        whenJust cancellable touchManagedPtr
        freeMem buffer'
        return result
     ) (do
        freeMem buffer'
     )

#if defined(ENABLE_OVERLOADING)
data SocketSendWithBlockingMethodInfo
instance (signature ~ (ByteString -> Bool -> Maybe (b) -> m DI.Int64), MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod SocketSendWithBlockingMethodInfo a signature where
    overloadedMethod = socketSendWithBlocking

instance O.OverloadedMethodInfo SocketSendWithBlockingMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketSendWithBlocking",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketSendWithBlocking"
        })


#endif

-- method Socket::set_blocking
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "blocking"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Whether to use blocking I/O or not."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_set_blocking" g_socket_set_blocking :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    CInt ->                                 -- blocking : TBasicType TBoolean
    IO ()

-- | Sets the blocking mode of the socket. In blocking mode
-- all operations (which don’t take an explicit blocking parameter) block until
-- they succeed or there is an error. In
-- non-blocking mode all functions return results immediately or
-- with a 'GI.Gio.Enums.IOErrorEnumWouldBlock' error.
-- 
-- All sockets are created in blocking mode. However, note that the
-- platform level socket is always non-blocking, and blocking mode
-- is a GSocket level feature.
-- 
-- /Since: 2.22/
socketSetBlocking ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> Bool
    -- ^ /@blocking@/: Whether to use blocking I\/O or not.
    -> m ()
socketSetBlocking :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> Bool -> m ()
socketSetBlocking a
socket Bool
blocking = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    let blocking' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
blocking
    g_socket_set_blocking socket' blocking'
    touchManagedPtr socket
    return ()

#if defined(ENABLE_OVERLOADING)
data SocketSetBlockingMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsSocket a) => O.OverloadedMethod SocketSetBlockingMethodInfo a signature where
    overloadedMethod = socketSetBlocking

instance O.OverloadedMethodInfo SocketSetBlockingMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketSetBlocking",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketSetBlocking"
        })


#endif

-- method Socket::set_broadcast
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "broadcast"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "whether @socket should allow sending to broadcast\n    addresses"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_set_broadcast" g_socket_set_broadcast :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    CInt ->                                 -- broadcast : TBasicType TBoolean
    IO ()

-- | Sets whether /@socket@/ should allow sending to broadcast addresses.
-- This is 'P.False' by default.
-- 
-- /Since: 2.32/
socketSetBroadcast ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> Bool
    -- ^ /@broadcast@/: whether /@socket@/ should allow sending to broadcast
    --     addresses
    -> m ()
socketSetBroadcast :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> Bool -> m ()
socketSetBroadcast a
socket Bool
broadcast = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    let broadcast' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
broadcast
    g_socket_set_broadcast socket' broadcast'
    touchManagedPtr socket
    return ()

#if defined(ENABLE_OVERLOADING)
data SocketSetBroadcastMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsSocket a) => O.OverloadedMethod SocketSetBroadcastMethodInfo a signature where
    overloadedMethod = socketSetBroadcast

instance O.OverloadedMethodInfo SocketSetBroadcastMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketSetBroadcast",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketSetBroadcast"
        })


#endif

-- method Socket::set_keepalive
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "keepalive"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Value for the keepalive flag"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_set_keepalive" g_socket_set_keepalive :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    CInt ->                                 -- keepalive : TBasicType TBoolean
    IO ()

-- | Sets or unsets the @/SO_KEEPALIVE/@ flag on the underlying socket. When
-- this flag is set on a socket, the system will attempt to verify that the
-- remote socket endpoint is still present if a sufficiently long period of
-- time passes with no data being exchanged. If the system is unable to
-- verify the presence of the remote endpoint, it will automatically close
-- the connection.
-- 
-- This option is only functional on certain kinds of sockets. (Notably,
-- 'GI.Gio.Enums.SocketProtocolTcp' sockets.)
-- 
-- The exact time between pings is system- and protocol-dependent, but will
-- normally be at least two hours. Most commonly, you would set this flag
-- on a server socket if you want to allow clients to remain idle for long
-- periods of time, but also want to ensure that connections are eventually
-- garbage-collected if clients crash or become unreachable.
-- 
-- /Since: 2.22/
socketSetKeepalive ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> Bool
    -- ^ /@keepalive@/: Value for the keepalive flag
    -> m ()
socketSetKeepalive :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> Bool -> m ()
socketSetKeepalive a
socket Bool
keepalive = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    let keepalive' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
keepalive
    g_socket_set_keepalive socket' keepalive'
    touchManagedPtr socket
    return ()

#if defined(ENABLE_OVERLOADING)
data SocketSetKeepaliveMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsSocket a) => O.OverloadedMethod SocketSetKeepaliveMethodInfo a signature where
    overloadedMethod = socketSetKeepalive

instance O.OverloadedMethodInfo SocketSetKeepaliveMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketSetKeepalive",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketSetKeepalive"
        })


#endif

-- method Socket::set_listen_backlog
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "backlog"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the maximum number of pending connections."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_set_listen_backlog" g_socket_set_listen_backlog :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Int32 ->                                -- backlog : TBasicType TInt
    IO ()

-- | Sets the maximum number of outstanding connections allowed
-- when listening on this socket. If more clients than this are
-- connecting to the socket and the application is not handling them
-- on time then the new connections will be refused.
-- 
-- Note that this must be called before 'GI.Gio.Objects.Socket.socketListen' and has no
-- effect if called after that.
-- 
-- /Since: 2.22/
socketSetListenBacklog ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> Int32
    -- ^ /@backlog@/: the maximum number of pending connections.
    -> m ()
socketSetListenBacklog :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> Int32 -> m ()
socketSetListenBacklog a
socket Int32
backlog = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    g_socket_set_listen_backlog socket' backlog
    touchManagedPtr socket
    return ()

#if defined(ENABLE_OVERLOADING)
data SocketSetListenBacklogMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsSocket a) => O.OverloadedMethod SocketSetListenBacklogMethodInfo a signature where
    overloadedMethod = socketSetListenBacklog

instance O.OverloadedMethodInfo SocketSetListenBacklogMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketSetListenBacklog",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketSetListenBacklog"
        })


#endif

-- method Socket::set_multicast_loopback
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "loopback"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "whether @socket should receive messages sent to its\n  multicast groups from the local host"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_set_multicast_loopback" g_socket_set_multicast_loopback :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    CInt ->                                 -- loopback : TBasicType TBoolean
    IO ()

-- | Sets whether outgoing multicast packets will be received by sockets
-- listening on that multicast address on the same host. This is 'P.True'
-- by default.
-- 
-- /Since: 2.32/
socketSetMulticastLoopback ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> Bool
    -- ^ /@loopback@/: whether /@socket@/ should receive messages sent to its
    --   multicast groups from the local host
    -> m ()
socketSetMulticastLoopback :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> Bool -> m ()
socketSetMulticastLoopback a
socket Bool
loopback = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    let loopback' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
loopback
    g_socket_set_multicast_loopback socket' loopback'
    touchManagedPtr socket
    return ()

#if defined(ENABLE_OVERLOADING)
data SocketSetMulticastLoopbackMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsSocket a) => O.OverloadedMethod SocketSetMulticastLoopbackMethodInfo a signature where
    overloadedMethod = socketSetMulticastLoopback

instance O.OverloadedMethodInfo SocketSetMulticastLoopbackMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketSetMulticastLoopback",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketSetMulticastLoopback"
        })


#endif

-- method Socket::set_multicast_ttl
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "ttl"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the time-to-live value for all multicast datagrams on @socket"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_set_multicast_ttl" g_socket_set_multicast_ttl :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Word32 ->                               -- ttl : TBasicType TUInt
    IO ()

-- | Sets the time-to-live for outgoing multicast datagrams on /@socket@/.
-- By default, this is 1, meaning that multicast packets will not leave
-- the local network.
-- 
-- /Since: 2.32/
socketSetMulticastTtl ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> Word32
    -- ^ /@ttl@/: the time-to-live value for all multicast datagrams on /@socket@/
    -> m ()
socketSetMulticastTtl :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> Word32 -> m ()
socketSetMulticastTtl a
socket Word32
ttl = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    g_socket_set_multicast_ttl socket' ttl
    touchManagedPtr socket
    return ()

#if defined(ENABLE_OVERLOADING)
data SocketSetMulticastTtlMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsSocket a) => O.OverloadedMethod SocketSetMulticastTtlMethodInfo a signature where
    overloadedMethod = socketSetMulticastTtl

instance O.OverloadedMethodInfo SocketSetMulticastTtlMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketSetMulticastTtl",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketSetMulticastTtl"
        })


#endif

-- method Socket::set_option
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "level"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the \"API level\" of the option (eg, `SOL_SOCKET`)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "optname"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the \"name\" of the option (eg, `SO_BROADCAST`)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the value to set the option to"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_set_option" g_socket_set_option :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Int32 ->                                -- level : TBasicType TInt
    Int32 ->                                -- optname : TBasicType TInt
    Int32 ->                                -- value : TBasicType TInt
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Sets the value of an integer-valued option on /@socket@/, as with
-- @/setsockopt()/@. (If you need to set a non-integer-valued option,
-- you will need to call @/setsockopt()/@ directly.)
-- 
-- The [\<gio\/gnetworking.h>][gio-gnetworking.h]
-- header pulls in system headers that will define most of the
-- standard\/portable socket options. For unusual socket protocols or
-- platform-dependent options, you may need to include additional
-- headers.
-- 
-- /Since: 2.36/
socketSetOption ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'
    -> Int32
    -- ^ /@level@/: the \"API level\" of the option (eg, @SOL_SOCKET@)
    -> Int32
    -- ^ /@optname@/: the \"name\" of the option (eg, @SO_BROADCAST@)
    -> Int32
    -- ^ /@value@/: the value to set the option to
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
socketSetOption :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> Int32 -> Int32 -> Int32 -> m ()
socketSetOption a
socket Int32
level Int32
optname Int32
value = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    onException (do
        _ <- propagateGError $ g_socket_set_option socket' level optname value
        touchManagedPtr socket
        return ()
     ) (do
        return ()
     )

#if defined(ENABLE_OVERLOADING)
data SocketSetOptionMethodInfo
instance (signature ~ (Int32 -> Int32 -> Int32 -> m ()), MonadIO m, IsSocket a) => O.OverloadedMethod SocketSetOptionMethodInfo a signature where
    overloadedMethod = socketSetOption

instance O.OverloadedMethodInfo SocketSetOptionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketSetOption",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketSetOption"
        })


#endif

-- method Socket::set_timeout
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "timeout"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the timeout for @socket, in seconds, or 0 for none"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_set_timeout" g_socket_set_timeout :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Word32 ->                               -- timeout : TBasicType TUInt
    IO ()

-- | Sets the time in seconds after which I\/O operations on /@socket@/ will
-- time out if they have not yet completed.
-- 
-- On a blocking socket, this means that any blocking t'GI.Gio.Objects.Socket.Socket'
-- operation will time out after /@timeout@/ seconds of inactivity,
-- returning 'GI.Gio.Enums.IOErrorEnumTimedOut'.
-- 
-- On a non-blocking socket, calls to 'GI.Gio.Objects.Socket.socketConditionWait' will
-- also fail with 'GI.Gio.Enums.IOErrorEnumTimedOut' after the given time. Sources
-- created with @/g_socket_create_source()/@ will trigger after
-- /@timeout@/ seconds of inactivity, with the requested condition
-- set, at which point calling 'GI.Gio.Objects.Socket.socketReceive', 'GI.Gio.Objects.Socket.socketSend',
-- 'GI.Gio.Objects.Socket.socketCheckConnectResult', etc, will fail with
-- 'GI.Gio.Enums.IOErrorEnumTimedOut'.
-- 
-- If /@timeout@/ is 0 (the default), operations will never time out
-- on their own.
-- 
-- Note that if an I\/O operation is interrupted by a signal, this may
-- cause the timeout to be reset.
-- 
-- /Since: 2.26/
socketSetTimeout ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> Word32
    -- ^ /@timeout@/: the timeout for /@socket@/, in seconds, or 0 for none
    -> m ()
socketSetTimeout :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> Word32 -> m ()
socketSetTimeout a
socket Word32
timeout = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    g_socket_set_timeout socket' timeout
    touchManagedPtr socket
    return ()

#if defined(ENABLE_OVERLOADING)
data SocketSetTimeoutMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsSocket a) => O.OverloadedMethod SocketSetTimeoutMethodInfo a signature where
    overloadedMethod = socketSetTimeout

instance O.OverloadedMethodInfo SocketSetTimeoutMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketSetTimeout",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketSetTimeout"
        })


#endif

-- method Socket::set_ttl
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "ttl"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the time-to-live value for all unicast packets on @socket"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_socket_set_ttl" g_socket_set_ttl :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    Word32 ->                               -- ttl : TBasicType TUInt
    IO ()

-- | Sets the time-to-live for outgoing unicast packets on /@socket@/.
-- By default the platform-specific default value is used.
-- 
-- /Since: 2.32/
socketSetTtl ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'.
    -> Word32
    -- ^ /@ttl@/: the time-to-live value for all unicast packets on /@socket@/
    -> m ()
socketSetTtl :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> Word32 -> m ()
socketSetTtl a
socket Word32
ttl = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    g_socket_set_ttl socket' ttl
    touchManagedPtr socket
    return ()

#if defined(ENABLE_OVERLOADING)
data SocketSetTtlMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsSocket a) => O.OverloadedMethod SocketSetTtlMethodInfo a signature where
    overloadedMethod = socketSetTtl

instance O.OverloadedMethodInfo SocketSetTtlMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketSetTtl",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketSetTtl"
        })


#endif

-- method Socket::shutdown
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket"
--           , argType = TInterface Name { namespace = "Gio" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSocket" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "shutdown_read"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether to shut down the read side"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "shutdown_write"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether to shut down the write side"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_socket_shutdown" g_socket_shutdown :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    CInt ->                                 -- shutdown_read : TBasicType TBoolean
    CInt ->                                 -- shutdown_write : TBasicType TBoolean
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Shut down part or all of a full-duplex connection.
-- 
-- If /@shutdownRead@/ is 'P.True' then the receiving side of the connection
-- is shut down, and further reading is disallowed.
-- 
-- If /@shutdownWrite@/ is 'P.True' then the sending side of the connection
-- is shut down, and further writing is disallowed.
-- 
-- It is allowed for both /@shutdownRead@/ and /@shutdownWrite@/ to be 'P.True'.
-- 
-- One example where it is useful to shut down only one side of a connection is
-- graceful disconnect for TCP connections where you close the sending side,
-- then wait for the other side to close the connection, thus ensuring that the
-- other side saw all sent data.
-- 
-- /Since: 2.22/
socketShutdown ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'
    -> Bool
    -- ^ /@shutdownRead@/: whether to shut down the read side
    -> Bool
    -- ^ /@shutdownWrite@/: whether to shut down the write side
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
socketShutdown :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> Bool -> Bool -> m ()
socketShutdown a
socket Bool
shutdownRead Bool
shutdownWrite = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    let shutdownRead' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
shutdownRead
    let shutdownWrite' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
shutdownWrite
    onException (do
        _ <- propagateGError $ g_socket_shutdown socket' shutdownRead' shutdownWrite'
        touchManagedPtr socket
        return ()
     ) (do
        return ()
     )

#if defined(ENABLE_OVERLOADING)
data SocketShutdownMethodInfo
instance (signature ~ (Bool -> Bool -> m ()), MonadIO m, IsSocket a) => O.OverloadedMethod SocketShutdownMethodInfo a signature where
    overloadedMethod = socketShutdown

instance O.OverloadedMethodInfo SocketShutdownMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketShutdown",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketShutdown"
        })


#endif

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

foreign import ccall "g_socket_speaks_ipv4" g_socket_speaks_ipv4 :: 
    Ptr Socket ->                           -- socket : TInterface (Name {namespace = "Gio", name = "Socket"})
    IO CInt

-- | Checks if a socket is capable of speaking IPv4.
-- 
-- IPv4 sockets are capable of speaking IPv4.  On some operating systems
-- and under some combinations of circumstances IPv6 sockets are also
-- capable of speaking IPv4.  See RFC 3493 section 3.7 for more
-- information.
-- 
-- No other types of sockets are currently considered as being capable
-- of speaking IPv4.
-- 
-- /Since: 2.22/
socketSpeaksIpv4 ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket@/: a t'GI.Gio.Objects.Socket.Socket'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if this socket can be used with IPv4.
socketSpeaksIpv4 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSocket a) =>
a -> m Bool
socketSpeaksIpv4 a
socket = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
    result <- g_socket_speaks_ipv4 socket'
    let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    touchManagedPtr socket
    return result'

#if defined(ENABLE_OVERLOADING)
data SocketSpeaksIpv4MethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSocket a) => O.OverloadedMethod SocketSpeaksIpv4MethodInfo a signature where
    overloadedMethod = socketSpeaksIpv4

instance O.OverloadedMethodInfo SocketSpeaksIpv4MethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Socket.socketSpeaksIpv4",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-Socket.html#v:socketSpeaksIpv4"
        })


#endif