{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Objects.Socket
(
Socket(..) ,
IsSocket ,
toSocket ,
#if defined(ENABLE_OVERLOADING)
ResolveSocketMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
SocketAcceptMethodInfo ,
#endif
socketAccept ,
#if defined(ENABLE_OVERLOADING)
SocketBindMethodInfo ,
#endif
socketBind ,
#if defined(ENABLE_OVERLOADING)
SocketCheckConnectResultMethodInfo ,
#endif
socketCheckConnectResult ,
#if defined(ENABLE_OVERLOADING)
SocketCloseMethodInfo ,
#endif
socketClose ,
#if defined(ENABLE_OVERLOADING)
SocketConditionCheckMethodInfo ,
#endif
socketConditionCheck ,
#if defined(ENABLE_OVERLOADING)
SocketConditionTimedWaitMethodInfo ,
#endif
socketConditionTimedWait ,
#if defined(ENABLE_OVERLOADING)
SocketConditionWaitMethodInfo ,
#endif
socketConditionWait ,
#if defined(ENABLE_OVERLOADING)
SocketConnectMethodInfo ,
#endif
socketConnect ,
#if defined(ENABLE_OVERLOADING)
SocketConnectionFactoryCreateConnectionMethodInfo,
#endif
socketConnectionFactoryCreateConnection ,
#if defined(ENABLE_OVERLOADING)
SocketGetAvailableBytesMethodInfo ,
#endif
socketGetAvailableBytes ,
#if defined(ENABLE_OVERLOADING)
SocketGetBlockingMethodInfo ,
#endif
socketGetBlocking ,
#if defined(ENABLE_OVERLOADING)
SocketGetBroadcastMethodInfo ,
#endif
socketGetBroadcast ,
#if defined(ENABLE_OVERLOADING)
SocketGetCredentialsMethodInfo ,
#endif
socketGetCredentials ,
#if defined(ENABLE_OVERLOADING)
SocketGetFamilyMethodInfo ,
#endif
socketGetFamily ,
#if defined(ENABLE_OVERLOADING)
SocketGetFdMethodInfo ,
#endif
socketGetFd ,
#if defined(ENABLE_OVERLOADING)
SocketGetKeepaliveMethodInfo ,
#endif
socketGetKeepalive ,
#if defined(ENABLE_OVERLOADING)
SocketGetListenBacklogMethodInfo ,
#endif
socketGetListenBacklog ,
#if defined(ENABLE_OVERLOADING)
SocketGetLocalAddressMethodInfo ,
#endif
socketGetLocalAddress ,
#if defined(ENABLE_OVERLOADING)
SocketGetMulticastLoopbackMethodInfo ,
#endif
socketGetMulticastLoopback ,
#if defined(ENABLE_OVERLOADING)
SocketGetMulticastTtlMethodInfo ,
#endif
socketGetMulticastTtl ,
#if defined(ENABLE_OVERLOADING)
SocketGetOptionMethodInfo ,
#endif
socketGetOption ,
#if defined(ENABLE_OVERLOADING)
SocketGetProtocolMethodInfo ,
#endif
socketGetProtocol ,
#if defined(ENABLE_OVERLOADING)
SocketGetRemoteAddressMethodInfo ,
#endif
socketGetRemoteAddress ,
#if defined(ENABLE_OVERLOADING)
SocketGetSocketTypeMethodInfo ,
#endif
socketGetSocketType ,
#if defined(ENABLE_OVERLOADING)
SocketGetTimeoutMethodInfo ,
#endif
socketGetTimeout ,
#if defined(ENABLE_OVERLOADING)
SocketGetTtlMethodInfo ,
#endif
socketGetTtl ,
#if defined(ENABLE_OVERLOADING)
SocketIsClosedMethodInfo ,
#endif
socketIsClosed ,
#if defined(ENABLE_OVERLOADING)
SocketIsConnectedMethodInfo ,
#endif
socketIsConnected ,
#if defined(ENABLE_OVERLOADING)
SocketJoinMulticastGroupMethodInfo ,
#endif
socketJoinMulticastGroup ,
#if defined(ENABLE_OVERLOADING)
SocketJoinMulticastGroupSsmMethodInfo ,
#endif
socketJoinMulticastGroupSsm ,
#if defined(ENABLE_OVERLOADING)
SocketLeaveMulticastGroupMethodInfo ,
#endif
socketLeaveMulticastGroup ,
#if defined(ENABLE_OVERLOADING)
SocketLeaveMulticastGroupSsmMethodInfo ,
#endif
socketLeaveMulticastGroupSsm ,
#if defined(ENABLE_OVERLOADING)
SocketListenMethodInfo ,
#endif
socketListen ,
socketNew ,
socketNewFromFd ,
#if defined(ENABLE_OVERLOADING)
SocketReceiveMethodInfo ,
#endif
socketReceive ,
#if defined(ENABLE_OVERLOADING)
SocketReceiveFromMethodInfo ,
#endif
socketReceiveFrom ,
#if defined(ENABLE_OVERLOADING)
SocketReceiveMessageMethodInfo ,
#endif
socketReceiveMessage ,
#if defined(ENABLE_OVERLOADING)
SocketReceiveMessagesMethodInfo ,
#endif
socketReceiveMessages ,
#if defined(ENABLE_OVERLOADING)
SocketReceiveWithBlockingMethodInfo ,
#endif
socketReceiveWithBlocking ,
#if defined(ENABLE_OVERLOADING)
SocketSendMethodInfo ,
#endif
socketSend ,
#if defined(ENABLE_OVERLOADING)
SocketSendMessageMethodInfo ,
#endif
socketSendMessage ,
#if defined(ENABLE_OVERLOADING)
SocketSendMessageWithTimeoutMethodInfo ,
#endif
socketSendMessageWithTimeout ,
#if defined(ENABLE_OVERLOADING)
SocketSendMessagesMethodInfo ,
#endif
socketSendMessages ,
#if defined(ENABLE_OVERLOADING)
SocketSendToMethodInfo ,
#endif
socketSendTo ,
#if defined(ENABLE_OVERLOADING)
SocketSendWithBlockingMethodInfo ,
#endif
socketSendWithBlocking ,
#if defined(ENABLE_OVERLOADING)
SocketSetBlockingMethodInfo ,
#endif
socketSetBlocking ,
#if defined(ENABLE_OVERLOADING)
SocketSetBroadcastMethodInfo ,
#endif
socketSetBroadcast ,
#if defined(ENABLE_OVERLOADING)
SocketSetKeepaliveMethodInfo ,
#endif
socketSetKeepalive ,
#if defined(ENABLE_OVERLOADING)
SocketSetListenBacklogMethodInfo ,
#endif
socketSetListenBacklog ,
#if defined(ENABLE_OVERLOADING)
SocketSetMulticastLoopbackMethodInfo ,
#endif
socketSetMulticastLoopback ,
#if defined(ENABLE_OVERLOADING)
SocketSetMulticastTtlMethodInfo ,
#endif
socketSetMulticastTtl ,
#if defined(ENABLE_OVERLOADING)
SocketSetOptionMethodInfo ,
#endif
socketSetOption ,
#if defined(ENABLE_OVERLOADING)
SocketSetTimeoutMethodInfo ,
#endif
socketSetTimeout ,
#if defined(ENABLE_OVERLOADING)
SocketSetTtlMethodInfo ,
#endif
socketSetTtl ,
#if defined(ENABLE_OVERLOADING)
SocketShutdownMethodInfo ,
#endif
socketShutdown ,
#if defined(ENABLE_OVERLOADING)
SocketSpeaksIpv4MethodInfo ,
#endif
socketSpeaksIpv4 ,
#if defined(ENABLE_OVERLOADING)
SocketBlockingPropertyInfo ,
#endif
constructSocketBlocking ,
getSocketBlocking ,
setSocketBlocking ,
#if defined(ENABLE_OVERLOADING)
socketBlocking ,
#endif
#if defined(ENABLE_OVERLOADING)
SocketBroadcastPropertyInfo ,
#endif
constructSocketBroadcast ,
getSocketBroadcast ,
setSocketBroadcast ,
#if defined(ENABLE_OVERLOADING)
socketBroadcast ,
#endif
#if defined(ENABLE_OVERLOADING)
SocketFamilyPropertyInfo ,
#endif
constructSocketFamily ,
getSocketFamily ,
#if defined(ENABLE_OVERLOADING)
socketFamily ,
#endif
#if defined(ENABLE_OVERLOADING)
SocketFdPropertyInfo ,
#endif
constructSocketFd ,
getSocketFd ,
#if defined(ENABLE_OVERLOADING)
socketFd ,
#endif
#if defined(ENABLE_OVERLOADING)
SocketKeepalivePropertyInfo ,
#endif
constructSocketKeepalive ,
getSocketKeepalive ,
setSocketKeepalive ,
#if defined(ENABLE_OVERLOADING)
socketKeepalive ,
#endif
#if defined(ENABLE_OVERLOADING)
SocketListenBacklogPropertyInfo ,
#endif
constructSocketListenBacklog ,
getSocketListenBacklog ,
setSocketListenBacklog ,
#if defined(ENABLE_OVERLOADING)
socketListenBacklog ,
#endif
#if defined(ENABLE_OVERLOADING)
SocketLocalAddressPropertyInfo ,
#endif
getSocketLocalAddress ,
#if defined(ENABLE_OVERLOADING)
socketLocalAddress ,
#endif
#if defined(ENABLE_OVERLOADING)
SocketMulticastLoopbackPropertyInfo ,
#endif
constructSocketMulticastLoopback ,
getSocketMulticastLoopback ,
setSocketMulticastLoopback ,
#if defined(ENABLE_OVERLOADING)
socketMulticastLoopback ,
#endif
#if defined(ENABLE_OVERLOADING)
SocketMulticastTtlPropertyInfo ,
#endif
constructSocketMulticastTtl ,
getSocketMulticastTtl ,
setSocketMulticastTtl ,
#if defined(ENABLE_OVERLOADING)
socketMulticastTtl ,
#endif
#if defined(ENABLE_OVERLOADING)
SocketProtocolPropertyInfo ,
#endif
constructSocketProtocol ,
getSocketProtocol ,
#if defined(ENABLE_OVERLOADING)
socketProtocol ,
#endif
#if defined(ENABLE_OVERLOADING)
SocketRemoteAddressPropertyInfo ,
#endif
getSocketRemoteAddress ,
#if defined(ENABLE_OVERLOADING)
socketRemoteAddress ,
#endif
#if defined(ENABLE_OVERLOADING)
SocketTimeoutPropertyInfo ,
#endif
constructSocketTimeout ,
getSocketTimeout ,
setSocketTimeout ,
#if defined(ENABLE_OVERLOADING)
socketTimeout ,
#endif
#if defined(ENABLE_OVERLOADING)
SocketTtlPropertyInfo ,
#endif
constructSocketTtl ,
getSocketTtl ,
setSocketTtl ,
#if defined(ENABLE_OVERLOADING)
socketTtl ,
#endif
#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.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GI.GLib.Flags as GLib.Flags
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
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
/= :: Socket -> Socket -> Bool
$c/= :: Socket -> Socket -> Bool
== :: Socket -> Socket -> Bool
$c== :: 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
instance B.GValue.IsGValue Socket where
toGValue :: Socket -> IO GValue
toGValue Socket
o = do
GType
gtype <- IO GType
c_g_socket_get_type
Socket -> (Ptr Socket -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Socket
o (GType -> (GValue -> Ptr Socket -> IO ()) -> Ptr Socket -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Socket -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO Socket
fromGValue GValue
gv = do
Ptr Socket
ptr <- GValue -> IO (Ptr Socket)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr Socket)
(ManagedPtr Socket -> Socket) -> Ptr Socket -> IO Socket
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Socket -> Socket
Socket Ptr Socket
ptr
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]
toSocket :: (MonadIO m, IsSocket o) => o -> m Socket
toSocket :: o -> m Socket
toSocket = IO Socket -> m Socket
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Socket -> m Socket) -> (o -> IO Socket) -> o -> m Socket
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Socket -> Socket) -> o -> IO Socket
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Socket -> Socket
Socket
#if defined(ENABLE_OVERLOADING)
type family ResolveSocketMethod (t :: Symbol) (o :: *) :: * 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 "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.MethodInfo info Socket p) => OL.IsLabel t (Socket -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
getSocketBlocking :: (MonadIO m, IsSocket o) => o -> m Bool
getSocketBlocking :: o -> m Bool
getSocketBlocking o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"blocking"
setSocketBlocking :: (MonadIO m, IsSocket o) => o -> Bool -> m ()
setSocketBlocking :: o -> Bool -> m ()
setSocketBlocking o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"blocking" Bool
val
constructSocketBlocking :: (IsSocket o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructSocketBlocking :: Bool -> m (GValueConstruct o)
constructSocketBlocking Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ 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
#endif
getSocketBroadcast :: (MonadIO m, IsSocket o) => o -> m Bool
getSocketBroadcast :: o -> m Bool
getSocketBroadcast o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"broadcast"
setSocketBroadcast :: (MonadIO m, IsSocket o) => o -> Bool -> m ()
setSocketBroadcast :: o -> Bool -> m ()
setSocketBroadcast o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"broadcast" Bool
val
constructSocketBroadcast :: (IsSocket o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructSocketBroadcast :: Bool -> m (GValueConstruct o)
constructSocketBroadcast Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ 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
#endif
getSocketFamily :: (MonadIO m, IsSocket o) => o -> m Gio.Enums.SocketFamily
getSocketFamily :: o -> m SocketFamily
getSocketFamily o
obj = IO SocketFamily -> m SocketFamily
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
$ o -> String -> IO SocketFamily
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"family"
constructSocketFamily :: (IsSocket o, MIO.MonadIO m) => Gio.Enums.SocketFamily -> m (GValueConstruct o)
constructSocketFamily :: SocketFamily -> m (GValueConstruct o)
constructSocketFamily SocketFamily
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ 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
#endif
getSocketFd :: (MonadIO m, IsSocket o) => o -> m Int32
getSocketFd :: o -> m Int32
getSocketFd o
obj = IO Int32 -> m Int32
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
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"fd"
constructSocketFd :: (IsSocket o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructSocketFd :: Int32 -> m (GValueConstruct o)
constructSocketFd Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ 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
#endif
getSocketKeepalive :: (MonadIO m, IsSocket o) => o -> m Bool
getSocketKeepalive :: o -> m Bool
getSocketKeepalive o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"keepalive"
setSocketKeepalive :: (MonadIO m, IsSocket o) => o -> Bool -> m ()
setSocketKeepalive :: o -> Bool -> m ()
setSocketKeepalive o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"keepalive" Bool
val
constructSocketKeepalive :: (IsSocket o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructSocketKeepalive :: Bool -> m (GValueConstruct o)
constructSocketKeepalive Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ 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
#endif
getSocketListenBacklog :: (MonadIO m, IsSocket o) => o -> m Int32
getSocketListenBacklog :: o -> m Int32
getSocketListenBacklog o
obj = IO Int32 -> m Int32
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
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"listen-backlog"
setSocketListenBacklog :: (MonadIO m, IsSocket o) => o -> Int32 -> m ()
setSocketListenBacklog :: o -> Int32 -> m ()
setSocketListenBacklog o
obj Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"listen-backlog" Int32
val
constructSocketListenBacklog :: (IsSocket o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructSocketListenBacklog :: Int32 -> m (GValueConstruct o)
constructSocketListenBacklog Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ 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
#endif
getSocketLocalAddress :: (MonadIO m, IsSocket o) => o -> m (Maybe Gio.SocketAddress.SocketAddress)
getSocketLocalAddress :: o -> m (Maybe SocketAddress)
getSocketLocalAddress o
obj = IO (Maybe SocketAddress) -> m (Maybe SocketAddress)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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
#endif
getSocketMulticastLoopback :: (MonadIO m, IsSocket o) => o -> m Bool
getSocketMulticastLoopback :: o -> m Bool
getSocketMulticastLoopback o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"multicast-loopback"
setSocketMulticastLoopback :: (MonadIO m, IsSocket o) => o -> Bool -> m ()
setSocketMulticastLoopback :: o -> Bool -> m ()
setSocketMulticastLoopback o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"multicast-loopback" Bool
val
constructSocketMulticastLoopback :: (IsSocket o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructSocketMulticastLoopback :: Bool -> m (GValueConstruct o)
constructSocketMulticastLoopback Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ 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
#endif
getSocketMulticastTtl :: (MonadIO m, IsSocket o) => o -> m Word32
getSocketMulticastTtl :: o -> m Word32
getSocketMulticastTtl o
obj = IO Word32 -> m Word32
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
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"multicast-ttl"
setSocketMulticastTtl :: (MonadIO m, IsSocket o) => o -> Word32 -> m ()
setSocketMulticastTtl :: o -> Word32 -> m ()
setSocketMulticastTtl o
obj Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"multicast-ttl" Word32
val
constructSocketMulticastTtl :: (IsSocket o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructSocketMulticastTtl :: Word32 -> m (GValueConstruct o)
constructSocketMulticastTtl Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ 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
#endif
getSocketProtocol :: (MonadIO m, IsSocket o) => o -> m Gio.Enums.SocketProtocol
getSocketProtocol :: o -> m SocketProtocol
getSocketProtocol o
obj = IO SocketProtocol -> m SocketProtocol
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
$ o -> String -> IO SocketProtocol
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"protocol"
constructSocketProtocol :: (IsSocket o, MIO.MonadIO m) => Gio.Enums.SocketProtocol -> m (GValueConstruct o)
constructSocketProtocol :: SocketProtocol -> m (GValueConstruct o)
constructSocketProtocol SocketProtocol
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ 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
#endif
getSocketRemoteAddress :: (MonadIO m, IsSocket o) => o -> m (Maybe Gio.SocketAddress.SocketAddress)
getSocketRemoteAddress :: o -> m (Maybe SocketAddress)
getSocketRemoteAddress o
obj = IO (Maybe SocketAddress) -> m (Maybe SocketAddress)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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
#endif
getSocketTimeout :: (MonadIO m, IsSocket o) => o -> m Word32
getSocketTimeout :: o -> m Word32
getSocketTimeout o
obj = IO Word32 -> m Word32
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
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"timeout"
setSocketTimeout :: (MonadIO m, IsSocket o) => o -> Word32 -> m ()
setSocketTimeout :: o -> Word32 -> m ()
setSocketTimeout o
obj Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"timeout" Word32
val
constructSocketTimeout :: (IsSocket o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructSocketTimeout :: Word32 -> m (GValueConstruct o)
constructSocketTimeout Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ 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
#endif
getSocketTtl :: (MonadIO m, IsSocket o) => o -> m Word32
getSocketTtl :: o -> m Word32
getSocketTtl o
obj = IO Word32 -> m Word32
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
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"ttl"
setSocketTtl :: (MonadIO m, IsSocket o) => o -> Word32 -> m ()
setSocketTtl :: o -> Word32 -> m ()
setSocketTtl o
obj Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"ttl" Word32
val
constructSocketTtl :: (IsSocket o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructSocketTtl :: Word32 -> m (GValueConstruct o)
constructSocketTtl Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ 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
#endif
getSocketType :: (MonadIO m, IsSocket o) => o -> m Gio.Enums.SocketType
getSocketType :: o -> m SocketType
getSocketType o
obj = IO SocketType -> m SocketType
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
$ o -> String -> IO SocketType
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"type"
constructSocketType :: (IsSocket o, MIO.MonadIO m) => Gio.Enums.SocketType -> m (GValueConstruct o)
constructSocketType :: SocketType -> m (GValueConstruct o)
constructSocketType SocketType
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ 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
#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, *)])
#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, *)])
#endif
foreign import ccall "g_socket_new" g_socket_new ::
CUInt ->
CUInt ->
CInt ->
Ptr (Ptr GError) ->
IO (Ptr Socket)
socketNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
Gio.Enums.SocketFamily
-> Gio.Enums.SocketType
-> Gio.Enums.SocketProtocol
-> m Socket
socketNew :: SocketFamily -> SocketType -> SocketProtocol -> m Socket
socketNew SocketFamily
family SocketType
type_ SocketProtocol
protocol = IO Socket -> m Socket
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Socket -> m Socket) -> IO Socket -> m Socket
forall a b. (a -> b) -> a -> b
$ do
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
Ptr Socket
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'
Text -> Ptr Socket -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"socketNew" Ptr Socket
result
Socket
result' <- ((ManagedPtr Socket -> Socket) -> Ptr Socket -> IO Socket
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Socket -> Socket
Socket) Ptr Socket
result
Socket -> IO Socket
forall (m :: * -> *) a. Monad m => a -> m a
return Socket
result'
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_socket_new_from_fd" g_socket_new_from_fd ::
Int32 ->
Ptr (Ptr GError) ->
IO (Ptr Socket)
socketNewFromFd ::
(B.CallStack.HasCallStack, MonadIO m) =>
Int32
-> m Socket
socketNewFromFd :: Int32 -> m Socket
socketNewFromFd Int32
fd = IO Socket -> m Socket
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Socket -> m Socket) -> IO Socket -> m Socket
forall a b. (a -> b) -> a -> b
$ do
IO Socket -> IO () -> IO Socket
forall a b. IO a -> IO b -> IO a
onException (do
Ptr Socket
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
Text -> Ptr Socket -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"socketNewFromFd" Ptr Socket
result
Socket
result' <- ((ManagedPtr Socket -> Socket) -> Ptr Socket -> IO Socket
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Socket -> Socket
Socket) Ptr Socket
result
Socket -> IO Socket
forall (m :: * -> *) a. Monad m => a -> m a
return Socket
result'
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_socket_accept" g_socket_accept ::
Ptr Socket ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO (Ptr Socket)
socketAccept ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) =>
a
-> Maybe (b)
-> m Socket
socketAccept :: a -> Maybe b -> m Socket
socketAccept a
socket Maybe b
cancellable = IO Socket -> m Socket
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Socket -> m Socket) -> IO Socket -> m Socket
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just b
jCancellable -> do
Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
IO Socket -> IO () -> IO Socket
forall a b. IO a -> IO b -> IO a
onException (do
Ptr Socket
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
$ Ptr Socket
-> Ptr Cancellable -> Ptr (Ptr GError) -> IO (Ptr Socket)
g_socket_accept Ptr Socket
socket' Ptr Cancellable
maybeCancellable
Text -> Ptr Socket -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"socketAccept" Ptr Socket
result
Socket
result' <- ((ManagedPtr Socket -> Socket) -> Ptr Socket -> IO Socket
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Socket -> Socket
Socket) Ptr Socket
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Socket -> IO Socket
forall (m :: * -> *) a. Monad m => a -> m a
return Socket
result'
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data SocketAcceptMethodInfo
instance (signature ~ (Maybe (b) -> m Socket), MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) => O.MethodInfo SocketAcceptMethodInfo a signature where
overloadedMethod = socketAccept
#endif
foreign import ccall "g_socket_bind" g_socket_bind ::
Ptr Socket ->
Ptr Gio.SocketAddress.SocketAddress ->
CInt ->
Ptr (Ptr GError) ->
IO CInt
socketBind ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.SocketAddress.IsSocketAddress b) =>
a
-> b
-> Bool
-> m ()
socketBind :: a -> b -> Bool -> m ()
socketBind a
socket b
address Bool
allowReuse = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
Ptr SocketAddress
address' <- b -> IO (Ptr SocketAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
address
let allowReuse' :: CInt
allowReuse' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
allowReuse
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Socket
-> Ptr SocketAddress -> CInt -> Ptr (Ptr GError) -> IO CInt
g_socket_bind Ptr Socket
socket' Ptr SocketAddress
address' CInt
allowReuse'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
address
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data SocketBindMethodInfo
instance (signature ~ (b -> Bool -> m ()), MonadIO m, IsSocket a, Gio.SocketAddress.IsSocketAddress b) => O.MethodInfo SocketBindMethodInfo a signature where
overloadedMethod = socketBind
#endif
foreign import ccall "g_socket_check_connect_result" g_socket_check_connect_result ::
Ptr Socket ->
Ptr (Ptr GError) ->
IO CInt
socketCheckConnectResult ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> m ()
socketCheckConnectResult :: a -> m ()
socketCheckConnectResult a
socket = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Socket -> Ptr (Ptr GError) -> IO CInt
g_socket_check_connect_result Ptr Socket
socket'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data SocketCheckConnectResultMethodInfo
instance (signature ~ (m ()), MonadIO m, IsSocket a) => O.MethodInfo SocketCheckConnectResultMethodInfo a signature where
overloadedMethod = socketCheckConnectResult
#endif
foreign import ccall "g_socket_close" g_socket_close ::
Ptr Socket ->
Ptr (Ptr GError) ->
IO CInt
socketClose ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> m ()
socketClose :: a -> m ()
socketClose a
socket = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Socket -> Ptr (Ptr GError) -> IO CInt
g_socket_close Ptr Socket
socket'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data SocketCloseMethodInfo
instance (signature ~ (m ()), MonadIO m, IsSocket a) => O.MethodInfo SocketCloseMethodInfo a signature where
overloadedMethod = socketClose
#endif
foreign import ccall "g_socket_condition_check" g_socket_condition_check ::
Ptr Socket ->
CUInt ->
IO CUInt
socketConditionCheck ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> [GLib.Flags.IOCondition]
-> m [GLib.Flags.IOCondition]
socketConditionCheck :: a -> [IOCondition] -> m [IOCondition]
socketConditionCheck a
socket [IOCondition]
condition = IO [IOCondition] -> m [IOCondition]
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
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
let condition' :: CUInt
condition' = [IOCondition] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [IOCondition]
condition
CUInt
result <- Ptr Socket -> CUInt -> IO CUInt
g_socket_condition_check Ptr Socket
socket' CUInt
condition'
let result' :: [IOCondition]
result' = CUInt -> [IOCondition]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
[IOCondition] -> IO [IOCondition]
forall (m :: * -> *) a. Monad m => a -> m a
return [IOCondition]
result'
#if defined(ENABLE_OVERLOADING)
data SocketConditionCheckMethodInfo
instance (signature ~ ([GLib.Flags.IOCondition] -> m [GLib.Flags.IOCondition]), MonadIO m, IsSocket a) => O.MethodInfo SocketConditionCheckMethodInfo a signature where
overloadedMethod = socketConditionCheck
#endif
foreign import ccall "g_socket_condition_timed_wait" g_socket_condition_timed_wait ::
Ptr Socket ->
CUInt ->
Int64 ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO CInt
socketConditionTimedWait ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) =>
a
-> [GLib.Flags.IOCondition]
-> Int64
-> Maybe (b)
-> m ()
socketConditionTimedWait :: a -> [IOCondition] -> Int64 -> Maybe b -> m ()
socketConditionTimedWait a
socket [IOCondition]
condition Int64
timeoutUs Maybe b
cancellable = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
let condition' :: CUInt
condition' = [IOCondition] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [IOCondition]
condition
Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just b
jCancellable -> do
Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Socket
-> CUInt -> Int64 -> Ptr Cancellable -> Ptr (Ptr GError) -> IO CInt
g_socket_condition_timed_wait Ptr Socket
socket' CUInt
condition' Int64
timeoutUs Ptr Cancellable
maybeCancellable
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
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.MethodInfo SocketConditionTimedWaitMethodInfo a signature where
overloadedMethod = socketConditionTimedWait
#endif
foreign import ccall "g_socket_condition_wait" g_socket_condition_wait ::
Ptr Socket ->
CUInt ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO CInt
socketConditionWait ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) =>
a
-> [GLib.Flags.IOCondition]
-> Maybe (b)
-> m ()
socketConditionWait :: a -> [IOCondition] -> Maybe b -> m ()
socketConditionWait a
socket [IOCondition]
condition Maybe b
cancellable = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
let condition' :: CUInt
condition' = [IOCondition] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [IOCondition]
condition
Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just b
jCancellable -> do
Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Socket
-> CUInt -> Ptr Cancellable -> Ptr (Ptr GError) -> IO CInt
g_socket_condition_wait Ptr Socket
socket' CUInt
condition' Ptr Cancellable
maybeCancellable
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data SocketConditionWaitMethodInfo
instance (signature ~ ([GLib.Flags.IOCondition] -> Maybe (b) -> m ()), MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) => O.MethodInfo SocketConditionWaitMethodInfo a signature where
overloadedMethod = socketConditionWait
#endif
foreign import ccall "g_socket_connect" g_socket_connect ::
Ptr Socket ->
Ptr Gio.SocketAddress.SocketAddress ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO CInt
socketConnect ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.SocketAddress.IsSocketAddress b, Gio.Cancellable.IsCancellable c) =>
a
-> b
-> Maybe (c)
-> m ()
socketConnect :: a -> b -> Maybe c -> m ()
socketConnect a
socket b
address Maybe c
cancellable = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
Ptr SocketAddress
address' <- b -> IO (Ptr SocketAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
address
Ptr Cancellable
maybeCancellable <- case Maybe c
cancellable of
Maybe c
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just c
jCancellable -> do
Ptr Cancellable
jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Socket
-> Ptr SocketAddress
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO CInt
g_socket_connect Ptr Socket
socket' Ptr SocketAddress
address' Ptr Cancellable
maybeCancellable
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
address
Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
cancellable c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
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.MethodInfo SocketConnectMethodInfo a signature where
overloadedMethod = socketConnect
#endif
foreign import ccall "g_socket_connection_factory_create_connection" g_socket_connection_factory_create_connection ::
Ptr Socket ->
IO (Ptr Gio.SocketConnection.SocketConnection)
socketConnectionFactoryCreateConnection ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> m Gio.SocketConnection.SocketConnection
socketConnectionFactoryCreateConnection :: a -> m SocketConnection
socketConnectionFactoryCreateConnection a
socket = IO SocketConnection -> m SocketConnection
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
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
Ptr SocketConnection
result <- Ptr Socket -> IO (Ptr SocketConnection)
g_socket_connection_factory_create_connection Ptr Socket
socket'
Text -> Ptr SocketConnection -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"socketConnectionFactoryCreateConnection" Ptr SocketConnection
result
SocketConnection
result' <- ((ManagedPtr SocketConnection -> SocketConnection)
-> Ptr SocketConnection -> IO SocketConnection
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr SocketConnection -> SocketConnection
Gio.SocketConnection.SocketConnection) Ptr SocketConnection
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
SocketConnection -> IO SocketConnection
forall (m :: * -> *) a. Monad m => a -> m a
return SocketConnection
result'
#if defined(ENABLE_OVERLOADING)
data SocketConnectionFactoryCreateConnectionMethodInfo
instance (signature ~ (m Gio.SocketConnection.SocketConnection), MonadIO m, IsSocket a) => O.MethodInfo SocketConnectionFactoryCreateConnectionMethodInfo a signature where
overloadedMethod = socketConnectionFactoryCreateConnection
#endif
foreign import ccall "g_socket_get_available_bytes" g_socket_get_available_bytes ::
Ptr Socket ->
IO Int64
socketGetAvailableBytes ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> m Int64
socketGetAvailableBytes :: a -> m Int64
socketGetAvailableBytes a
socket = IO Int64 -> m Int64
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
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
Int64
result <- Ptr Socket -> IO Int64
g_socket_get_available_bytes Ptr Socket
socket'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
Int64 -> IO Int64
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
result
#if defined(ENABLE_OVERLOADING)
data SocketGetAvailableBytesMethodInfo
instance (signature ~ (m Int64), MonadIO m, IsSocket a) => O.MethodInfo SocketGetAvailableBytesMethodInfo a signature where
overloadedMethod = socketGetAvailableBytes
#endif
foreign import ccall "g_socket_get_blocking" g_socket_get_blocking ::
Ptr Socket ->
IO CInt
socketGetBlocking ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> m Bool
socketGetBlocking :: a -> m Bool
socketGetBlocking a
socket = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
CInt
result <- Ptr Socket -> IO CInt
g_socket_get_blocking Ptr Socket
socket'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data SocketGetBlockingMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSocket a) => O.MethodInfo SocketGetBlockingMethodInfo a signature where
overloadedMethod = socketGetBlocking
#endif
foreign import ccall "g_socket_get_broadcast" g_socket_get_broadcast ::
Ptr Socket ->
IO CInt
socketGetBroadcast ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> m Bool
socketGetBroadcast :: a -> m Bool
socketGetBroadcast a
socket = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
CInt
result <- Ptr Socket -> IO CInt
g_socket_get_broadcast Ptr Socket
socket'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data SocketGetBroadcastMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSocket a) => O.MethodInfo SocketGetBroadcastMethodInfo a signature where
overloadedMethod = socketGetBroadcast
#endif
foreign import ccall "g_socket_get_credentials" g_socket_get_credentials ::
Ptr Socket ->
Ptr (Ptr GError) ->
IO (Ptr Gio.Credentials.Credentials)
socketGetCredentials ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> m Gio.Credentials.Credentials
socketGetCredentials :: a -> m Credentials
socketGetCredentials a
socket = IO Credentials -> m Credentials
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
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
IO Credentials -> IO () -> IO Credentials
forall a b. IO a -> IO b -> IO a
onException (do
Ptr Credentials
result <- (Ptr (Ptr GError) -> IO (Ptr Credentials)) -> IO (Ptr Credentials)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Credentials))
-> IO (Ptr Credentials))
-> (Ptr (Ptr GError) -> IO (Ptr Credentials))
-> IO (Ptr Credentials)
forall a b. (a -> b) -> a -> b
$ Ptr Socket -> Ptr (Ptr GError) -> IO (Ptr Credentials)
g_socket_get_credentials Ptr Socket
socket'
Text -> Ptr Credentials -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"socketGetCredentials" Ptr Credentials
result
Credentials
result' <- ((ManagedPtr Credentials -> Credentials)
-> Ptr Credentials -> IO Credentials
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Credentials -> Credentials
Gio.Credentials.Credentials) Ptr Credentials
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
Credentials -> IO Credentials
forall (m :: * -> *) a. Monad m => a -> m a
return Credentials
result'
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data SocketGetCredentialsMethodInfo
instance (signature ~ (m Gio.Credentials.Credentials), MonadIO m, IsSocket a) => O.MethodInfo SocketGetCredentialsMethodInfo a signature where
overloadedMethod = socketGetCredentials
#endif
foreign import ccall "g_socket_get_family" g_socket_get_family ::
Ptr Socket ->
IO CUInt
socketGetFamily ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> m Gio.Enums.SocketFamily
socketGetFamily :: a -> m SocketFamily
socketGetFamily a
socket = IO SocketFamily -> m SocketFamily
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
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
CUInt
result <- Ptr Socket -> IO CUInt
g_socket_get_family Ptr Socket
socket'
let result' :: SocketFamily
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
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
SocketFamily -> IO SocketFamily
forall (m :: * -> *) a. Monad m => a -> m a
return SocketFamily
result'
#if defined(ENABLE_OVERLOADING)
data SocketGetFamilyMethodInfo
instance (signature ~ (m Gio.Enums.SocketFamily), MonadIO m, IsSocket a) => O.MethodInfo SocketGetFamilyMethodInfo a signature where
overloadedMethod = socketGetFamily
#endif
foreign import ccall "g_socket_get_fd" g_socket_get_fd ::
Ptr Socket ->
IO Int32
socketGetFd ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> m Int32
socketGetFd :: a -> m Int32
socketGetFd a
socket = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
Int32
result <- Ptr Socket -> IO Int32
g_socket_get_fd Ptr Socket
socket'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data SocketGetFdMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsSocket a) => O.MethodInfo SocketGetFdMethodInfo a signature where
overloadedMethod = socketGetFd
#endif
foreign import ccall "g_socket_get_keepalive" g_socket_get_keepalive ::
Ptr Socket ->
IO CInt
socketGetKeepalive ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> m Bool
socketGetKeepalive :: a -> m Bool
socketGetKeepalive a
socket = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
CInt
result <- Ptr Socket -> IO CInt
g_socket_get_keepalive Ptr Socket
socket'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data SocketGetKeepaliveMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSocket a) => O.MethodInfo SocketGetKeepaliveMethodInfo a signature where
overloadedMethod = socketGetKeepalive
#endif
foreign import ccall "g_socket_get_listen_backlog" g_socket_get_listen_backlog ::
Ptr Socket ->
IO Int32
socketGetListenBacklog ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> m Int32
socketGetListenBacklog :: a -> m Int32
socketGetListenBacklog a
socket = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
Int32
result <- Ptr Socket -> IO Int32
g_socket_get_listen_backlog Ptr Socket
socket'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data SocketGetListenBacklogMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsSocket a) => O.MethodInfo SocketGetListenBacklogMethodInfo a signature where
overloadedMethod = socketGetListenBacklog
#endif
foreign import ccall "g_socket_get_local_address" g_socket_get_local_address ::
Ptr Socket ->
Ptr (Ptr GError) ->
IO (Ptr Gio.SocketAddress.SocketAddress)
socketGetLocalAddress ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> m Gio.SocketAddress.SocketAddress
socketGetLocalAddress :: a -> m SocketAddress
socketGetLocalAddress a
socket = IO SocketAddress -> m SocketAddress
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
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
IO SocketAddress -> IO () -> IO SocketAddress
forall a b. IO a -> IO b -> IO a
onException (do
Ptr SocketAddress
result <- (Ptr (Ptr GError) -> IO (Ptr SocketAddress))
-> IO (Ptr SocketAddress)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr SocketAddress))
-> IO (Ptr SocketAddress))
-> (Ptr (Ptr GError) -> IO (Ptr SocketAddress))
-> IO (Ptr SocketAddress)
forall a b. (a -> b) -> a -> b
$ Ptr Socket -> Ptr (Ptr GError) -> IO (Ptr SocketAddress)
g_socket_get_local_address Ptr Socket
socket'
Text -> Ptr SocketAddress -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"socketGetLocalAddress" Ptr SocketAddress
result
SocketAddress
result' <- ((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
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
SocketAddress -> IO SocketAddress
forall (m :: * -> *) a. Monad m => a -> m a
return SocketAddress
result'
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data SocketGetLocalAddressMethodInfo
instance (signature ~ (m Gio.SocketAddress.SocketAddress), MonadIO m, IsSocket a) => O.MethodInfo SocketGetLocalAddressMethodInfo a signature where
overloadedMethod = socketGetLocalAddress
#endif
foreign import ccall "g_socket_get_multicast_loopback" g_socket_get_multicast_loopback ::
Ptr Socket ->
IO CInt
socketGetMulticastLoopback ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> m Bool
socketGetMulticastLoopback :: a -> m Bool
socketGetMulticastLoopback a
socket = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
CInt
result <- Ptr Socket -> IO CInt
g_socket_get_multicast_loopback Ptr Socket
socket'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data SocketGetMulticastLoopbackMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSocket a) => O.MethodInfo SocketGetMulticastLoopbackMethodInfo a signature where
overloadedMethod = socketGetMulticastLoopback
#endif
foreign import ccall "g_socket_get_multicast_ttl" g_socket_get_multicast_ttl ::
Ptr Socket ->
IO Word32
socketGetMulticastTtl ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> m Word32
socketGetMulticastTtl :: a -> m Word32
socketGetMulticastTtl a
socket = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
Word32
result <- Ptr Socket -> IO Word32
g_socket_get_multicast_ttl Ptr Socket
socket'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data SocketGetMulticastTtlMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSocket a) => O.MethodInfo SocketGetMulticastTtlMethodInfo a signature where
overloadedMethod = socketGetMulticastTtl
#endif
foreign import ccall "g_socket_get_option" g_socket_get_option ::
Ptr Socket ->
Int32 ->
Int32 ->
Ptr Int32 ->
Ptr (Ptr GError) ->
IO CInt
socketGetOption ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> Int32
-> Int32
-> m (Int32)
socketGetOption :: a -> Int32 -> Int32 -> m Int32
socketGetOption a
socket Int32
level Int32
optname = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
Ptr Int32
value <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
IO Int32 -> IO () -> IO Int32
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Socket
-> Int32 -> Int32 -> Ptr Int32 -> Ptr (Ptr GError) -> IO CInt
g_socket_get_option Ptr Socket
socket' Int32
level Int32
optname Ptr Int32
value
Int32
value' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
value
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
value
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
value'
) (do
Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
value
)
#if defined(ENABLE_OVERLOADING)
data SocketGetOptionMethodInfo
instance (signature ~ (Int32 -> Int32 -> m (Int32)), MonadIO m, IsSocket a) => O.MethodInfo SocketGetOptionMethodInfo a signature where
overloadedMethod = socketGetOption
#endif
foreign import ccall "g_socket_get_protocol" g_socket_get_protocol ::
Ptr Socket ->
IO CInt
socketGetProtocol ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> m Gio.Enums.SocketProtocol
socketGetProtocol :: a -> m SocketProtocol
socketGetProtocol a
socket = IO SocketProtocol -> m SocketProtocol
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
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
CInt
result <- Ptr Socket -> IO CInt
g_socket_get_protocol Ptr Socket
socket'
let result' :: SocketProtocol
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
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
SocketProtocol -> IO SocketProtocol
forall (m :: * -> *) a. Monad m => a -> m a
return SocketProtocol
result'
#if defined(ENABLE_OVERLOADING)
data SocketGetProtocolMethodInfo
instance (signature ~ (m Gio.Enums.SocketProtocol), MonadIO m, IsSocket a) => O.MethodInfo SocketGetProtocolMethodInfo a signature where
overloadedMethod = socketGetProtocol
#endif
foreign import ccall "g_socket_get_remote_address" g_socket_get_remote_address ::
Ptr Socket ->
Ptr (Ptr GError) ->
IO (Ptr Gio.SocketAddress.SocketAddress)
socketGetRemoteAddress ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> m Gio.SocketAddress.SocketAddress
socketGetRemoteAddress :: a -> m SocketAddress
socketGetRemoteAddress a
socket = IO SocketAddress -> m SocketAddress
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
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
IO SocketAddress -> IO () -> IO SocketAddress
forall a b. IO a -> IO b -> IO a
onException (do
Ptr SocketAddress
result <- (Ptr (Ptr GError) -> IO (Ptr SocketAddress))
-> IO (Ptr SocketAddress)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr SocketAddress))
-> IO (Ptr SocketAddress))
-> (Ptr (Ptr GError) -> IO (Ptr SocketAddress))
-> IO (Ptr SocketAddress)
forall a b. (a -> b) -> a -> b
$ Ptr Socket -> Ptr (Ptr GError) -> IO (Ptr SocketAddress)
g_socket_get_remote_address Ptr Socket
socket'
Text -> Ptr SocketAddress -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"socketGetRemoteAddress" Ptr SocketAddress
result
SocketAddress
result' <- ((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
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
SocketAddress -> IO SocketAddress
forall (m :: * -> *) a. Monad m => a -> m a
return SocketAddress
result'
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data SocketGetRemoteAddressMethodInfo
instance (signature ~ (m Gio.SocketAddress.SocketAddress), MonadIO m, IsSocket a) => O.MethodInfo SocketGetRemoteAddressMethodInfo a signature where
overloadedMethod = socketGetRemoteAddress
#endif
foreign import ccall "g_socket_get_socket_type" g_socket_get_socket_type ::
Ptr Socket ->
IO CUInt
socketGetSocketType ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> m Gio.Enums.SocketType
socketGetSocketType :: a -> m SocketType
socketGetSocketType a
socket = IO SocketType -> m SocketType
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
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
CUInt
result <- Ptr Socket -> IO CUInt
g_socket_get_socket_type Ptr Socket
socket'
let result' :: SocketType
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
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
SocketType -> IO SocketType
forall (m :: * -> *) a. Monad m => a -> m a
return SocketType
result'
#if defined(ENABLE_OVERLOADING)
data SocketGetSocketTypeMethodInfo
instance (signature ~ (m Gio.Enums.SocketType), MonadIO m, IsSocket a) => O.MethodInfo SocketGetSocketTypeMethodInfo a signature where
overloadedMethod = socketGetSocketType
#endif
foreign import ccall "g_socket_get_timeout" g_socket_get_timeout ::
Ptr Socket ->
IO Word32
socketGetTimeout ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> m Word32
socketGetTimeout :: a -> m Word32
socketGetTimeout a
socket = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
Word32
result <- Ptr Socket -> IO Word32
g_socket_get_timeout Ptr Socket
socket'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data SocketGetTimeoutMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSocket a) => O.MethodInfo SocketGetTimeoutMethodInfo a signature where
overloadedMethod = socketGetTimeout
#endif
foreign import ccall "g_socket_get_ttl" g_socket_get_ttl ::
Ptr Socket ->
IO Word32
socketGetTtl ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> m Word32
socketGetTtl :: a -> m Word32
socketGetTtl a
socket = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
Word32
result <- Ptr Socket -> IO Word32
g_socket_get_ttl Ptr Socket
socket'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data SocketGetTtlMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSocket a) => O.MethodInfo SocketGetTtlMethodInfo a signature where
overloadedMethod = socketGetTtl
#endif
foreign import ccall "g_socket_is_closed" g_socket_is_closed ::
Ptr Socket ->
IO CInt
socketIsClosed ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> m Bool
socketIsClosed :: a -> m Bool
socketIsClosed a
socket = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
CInt
result <- Ptr Socket -> IO CInt
g_socket_is_closed Ptr Socket
socket'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data SocketIsClosedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSocket a) => O.MethodInfo SocketIsClosedMethodInfo a signature where
overloadedMethod = socketIsClosed
#endif
foreign import ccall "g_socket_is_connected" g_socket_is_connected ::
Ptr Socket ->
IO CInt
socketIsConnected ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> m Bool
socketIsConnected :: a -> m Bool
socketIsConnected a
socket = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
CInt
result <- Ptr Socket -> IO CInt
g_socket_is_connected Ptr Socket
socket'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data SocketIsConnectedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSocket a) => O.MethodInfo SocketIsConnectedMethodInfo a signature where
overloadedMethod = socketIsConnected
#endif
foreign import ccall "g_socket_join_multicast_group" g_socket_join_multicast_group ::
Ptr Socket ->
Ptr Gio.InetAddress.InetAddress ->
CInt ->
CString ->
Ptr (Ptr GError) ->
IO CInt
socketJoinMulticastGroup ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.InetAddress.IsInetAddress b) =>
a
-> b
-> Bool
-> Maybe (T.Text)
-> m ()
socketJoinMulticastGroup :: a -> b -> Bool -> Maybe Text -> m ()
socketJoinMulticastGroup a
socket b
group Bool
sourceSpecific Maybe Text
iface = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
Ptr InetAddress
group' <- b -> IO (Ptr InetAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
group
let sourceSpecific' :: CInt
sourceSpecific' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
sourceSpecific
Ptr CChar
maybeIface <- case Maybe Text
iface of
Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
Just Text
jIface -> do
Ptr CChar
jIface' <- Text -> IO (Ptr CChar)
textToCString Text
jIface
Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jIface'
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Socket
-> Ptr InetAddress
-> CInt
-> Ptr CChar
-> Ptr (Ptr GError)
-> IO CInt
g_socket_join_multicast_group Ptr Socket
socket' Ptr InetAddress
group' CInt
sourceSpecific' Ptr CChar
maybeIface
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
group
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeIface
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeIface
)
#if defined(ENABLE_OVERLOADING)
data SocketJoinMulticastGroupMethodInfo
instance (signature ~ (b -> Bool -> Maybe (T.Text) -> m ()), MonadIO m, IsSocket a, Gio.InetAddress.IsInetAddress b) => O.MethodInfo SocketJoinMulticastGroupMethodInfo a signature where
overloadedMethod = socketJoinMulticastGroup
#endif
foreign import ccall "g_socket_join_multicast_group_ssm" g_socket_join_multicast_group_ssm ::
Ptr Socket ->
Ptr Gio.InetAddress.InetAddress ->
Ptr Gio.InetAddress.InetAddress ->
CString ->
Ptr (Ptr GError) ->
IO CInt
socketJoinMulticastGroupSsm ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.InetAddress.IsInetAddress b, Gio.InetAddress.IsInetAddress c) =>
a
-> b
-> Maybe (c)
-> Maybe (T.Text)
-> m ()
socketJoinMulticastGroupSsm :: a -> b -> Maybe c -> Maybe Text -> m ()
socketJoinMulticastGroupSsm a
socket b
group Maybe c
sourceSpecific Maybe Text
iface = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
Ptr InetAddress
group' <- b -> IO (Ptr InetAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
group
Ptr InetAddress
maybeSourceSpecific <- case Maybe c
sourceSpecific of
Maybe c
Nothing -> Ptr InetAddress -> IO (Ptr InetAddress)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr InetAddress
forall a. Ptr a
nullPtr
Just c
jSourceSpecific -> do
Ptr InetAddress
jSourceSpecific' <- c -> IO (Ptr InetAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jSourceSpecific
Ptr InetAddress -> IO (Ptr InetAddress)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr InetAddress
jSourceSpecific'
Ptr CChar
maybeIface <- case Maybe Text
iface of
Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
Just Text
jIface -> do
Ptr CChar
jIface' <- Text -> IO (Ptr CChar)
textToCString Text
jIface
Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jIface'
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Socket
-> Ptr InetAddress
-> Ptr InetAddress
-> Ptr CChar
-> Ptr (Ptr GError)
-> IO CInt
g_socket_join_multicast_group_ssm Ptr Socket
socket' Ptr InetAddress
group' Ptr InetAddress
maybeSourceSpecific Ptr CChar
maybeIface
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
group
Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
sourceSpecific c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeIface
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
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.MethodInfo SocketJoinMulticastGroupSsmMethodInfo a signature where
overloadedMethod = socketJoinMulticastGroupSsm
#endif
foreign import ccall "g_socket_leave_multicast_group" g_socket_leave_multicast_group ::
Ptr Socket ->
Ptr Gio.InetAddress.InetAddress ->
CInt ->
CString ->
Ptr (Ptr GError) ->
IO CInt
socketLeaveMulticastGroup ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.InetAddress.IsInetAddress b) =>
a
-> b
-> Bool
-> Maybe (T.Text)
-> m ()
socketLeaveMulticastGroup :: a -> b -> Bool -> Maybe Text -> m ()
socketLeaveMulticastGroup a
socket b
group Bool
sourceSpecific Maybe Text
iface = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
Ptr InetAddress
group' <- b -> IO (Ptr InetAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
group
let sourceSpecific' :: CInt
sourceSpecific' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
sourceSpecific
Ptr CChar
maybeIface <- case Maybe Text
iface of
Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
Just Text
jIface -> do
Ptr CChar
jIface' <- Text -> IO (Ptr CChar)
textToCString Text
jIface
Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jIface'
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Socket
-> Ptr InetAddress
-> CInt
-> Ptr CChar
-> Ptr (Ptr GError)
-> IO CInt
g_socket_leave_multicast_group Ptr Socket
socket' Ptr InetAddress
group' CInt
sourceSpecific' Ptr CChar
maybeIface
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
group
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeIface
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeIface
)
#if defined(ENABLE_OVERLOADING)
data SocketLeaveMulticastGroupMethodInfo
instance (signature ~ (b -> Bool -> Maybe (T.Text) -> m ()), MonadIO m, IsSocket a, Gio.InetAddress.IsInetAddress b) => O.MethodInfo SocketLeaveMulticastGroupMethodInfo a signature where
overloadedMethod = socketLeaveMulticastGroup
#endif
foreign import ccall "g_socket_leave_multicast_group_ssm" g_socket_leave_multicast_group_ssm ::
Ptr Socket ->
Ptr Gio.InetAddress.InetAddress ->
Ptr Gio.InetAddress.InetAddress ->
CString ->
Ptr (Ptr GError) ->
IO CInt
socketLeaveMulticastGroupSsm ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.InetAddress.IsInetAddress b, Gio.InetAddress.IsInetAddress c) =>
a
-> b
-> Maybe (c)
-> Maybe (T.Text)
-> m ()
socketLeaveMulticastGroupSsm :: a -> b -> Maybe c -> Maybe Text -> m ()
socketLeaveMulticastGroupSsm a
socket b
group Maybe c
sourceSpecific Maybe Text
iface = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
Ptr InetAddress
group' <- b -> IO (Ptr InetAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
group
Ptr InetAddress
maybeSourceSpecific <- case Maybe c
sourceSpecific of
Maybe c
Nothing -> Ptr InetAddress -> IO (Ptr InetAddress)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr InetAddress
forall a. Ptr a
nullPtr
Just c
jSourceSpecific -> do
Ptr InetAddress
jSourceSpecific' <- c -> IO (Ptr InetAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jSourceSpecific
Ptr InetAddress -> IO (Ptr InetAddress)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr InetAddress
jSourceSpecific'
Ptr CChar
maybeIface <- case Maybe Text
iface of
Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
Just Text
jIface -> do
Ptr CChar
jIface' <- Text -> IO (Ptr CChar)
textToCString Text
jIface
Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jIface'
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Socket
-> Ptr InetAddress
-> Ptr InetAddress
-> Ptr CChar
-> Ptr (Ptr GError)
-> IO CInt
g_socket_leave_multicast_group_ssm Ptr Socket
socket' Ptr InetAddress
group' Ptr InetAddress
maybeSourceSpecific Ptr CChar
maybeIface
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
group
Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
sourceSpecific c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeIface
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
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.MethodInfo SocketLeaveMulticastGroupSsmMethodInfo a signature where
overloadedMethod = socketLeaveMulticastGroupSsm
#endif
foreign import ccall "g_socket_listen" g_socket_listen ::
Ptr Socket ->
Ptr (Ptr GError) ->
IO CInt
socketListen ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> m ()
socketListen :: a -> m ()
socketListen a
socket = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Socket -> Ptr (Ptr GError) -> IO CInt
g_socket_listen Ptr Socket
socket'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data SocketListenMethodInfo
instance (signature ~ (m ()), MonadIO m, IsSocket a) => O.MethodInfo SocketListenMethodInfo a signature where
overloadedMethod = socketListen
#endif
foreign import ccall "g_socket_receive" g_socket_receive ::
Ptr Socket ->
Ptr Word8 ->
Word64 ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO Int64
socketReceive ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) =>
a
-> ByteString
-> Maybe (b)
-> m Int64
socketReceive :: a -> ByteString -> Maybe b -> m Int64
socketReceive a
socket ByteString
buffer Maybe b
cancellable = IO Int64 -> m Int64
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 :: Word64
size = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
buffer
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
Ptr Word8
buffer' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
buffer
Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just b
jCancellable -> do
Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
IO Int64 -> IO () -> IO Int64
forall a b. IO a -> IO b -> IO a
onException (do
Int64
result <- (Ptr (Ptr GError) -> IO Int64) -> IO Int64
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO Int64) -> IO Int64)
-> (Ptr (Ptr GError) -> IO Int64) -> IO Int64
forall a b. (a -> b) -> a -> b
$ Ptr Socket
-> Ptr Word8
-> Word64
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO Int64
g_socket_receive Ptr Socket
socket' Ptr Word8
buffer' Word64
size Ptr Cancellable
maybeCancellable
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
buffer'
Int64 -> IO Int64
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
result
) (do
Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
buffer'
)
#if defined(ENABLE_OVERLOADING)
data SocketReceiveMethodInfo
instance (signature ~ (ByteString -> Maybe (b) -> m Int64), MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) => O.MethodInfo SocketReceiveMethodInfo a signature where
overloadedMethod = socketReceive
#endif
foreign import ccall "g_socket_receive_from" g_socket_receive_from ::
Ptr Socket ->
Ptr (Ptr Gio.SocketAddress.SocketAddress) ->
Ptr Word8 ->
Word64 ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO Int64
socketReceiveFrom ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) =>
a
-> ByteString
-> Maybe (b)
-> m ((Int64, Gio.SocketAddress.SocketAddress))
socketReceiveFrom :: a -> ByteString -> Maybe b -> m (Int64, SocketAddress)
socketReceiveFrom a
socket ByteString
buffer Maybe b
cancellable = IO (Int64, SocketAddress) -> m (Int64, SocketAddress)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int64, SocketAddress) -> m (Int64, SocketAddress))
-> IO (Int64, SocketAddress) -> m (Int64, SocketAddress)
forall a b. (a -> b) -> a -> b
$ do
let size :: Word64
size = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
buffer
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
Ptr (Ptr SocketAddress)
address <- IO (Ptr (Ptr SocketAddress))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (Ptr Gio.SocketAddress.SocketAddress))
Ptr Word8
buffer' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
buffer
Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just b
jCancellable -> do
Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
IO (Int64, SocketAddress) -> IO () -> IO (Int64, SocketAddress)
forall a b. IO a -> IO b -> IO a
onException (do
Int64
result <- (Ptr (Ptr GError) -> IO Int64) -> IO Int64
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO Int64) -> IO Int64)
-> (Ptr (Ptr GError) -> IO Int64) -> IO Int64
forall a b. (a -> b) -> a -> b
$ Ptr Socket
-> Ptr (Ptr SocketAddress)
-> Ptr Word8
-> Word64
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO Int64
g_socket_receive_from Ptr Socket
socket' Ptr (Ptr SocketAddress)
address Ptr Word8
buffer' Word64
size Ptr Cancellable
maybeCancellable
Ptr SocketAddress
address' <- Ptr (Ptr SocketAddress) -> IO (Ptr SocketAddress)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr SocketAddress)
address
SocketAddress
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'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Ptr (Ptr SocketAddress) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr SocketAddress)
address
Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
buffer'
(Int64, SocketAddress) -> IO (Int64, SocketAddress)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int64
result, SocketAddress
address'')
) (do
Ptr (Ptr SocketAddress) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr SocketAddress)
address
Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
buffer'
)
#if defined(ENABLE_OVERLOADING)
data SocketReceiveFromMethodInfo
instance (signature ~ (ByteString -> Maybe (b) -> m ((Int64, Gio.SocketAddress.SocketAddress))), MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) => O.MethodInfo SocketReceiveFromMethodInfo a signature where
overloadedMethod = socketReceiveFrom
#endif
foreign import ccall "g_socket_receive_message" g_socket_receive_message ::
Ptr Socket ->
Ptr (Ptr Gio.SocketAddress.SocketAddress) ->
Ptr Gio.InputVector.InputVector ->
Int32 ->
Ptr (Ptr (Ptr Gio.SocketControlMessage.SocketControlMessage)) ->
Ptr Int32 ->
Ptr Int32 ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO Int64
socketReceiveMessage ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) =>
a
-> [Gio.InputVector.InputVector]
-> Int32
-> Maybe (b)
-> m ((Int64, Maybe Gio.SocketAddress.SocketAddress, Maybe [Gio.SocketControlMessage.SocketControlMessage], Int32))
socketReceiveMessage :: 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 (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 (t :: * -> *) a. Foldable t => t a -> Int
P.length [InputVector]
vectors
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
Ptr (Ptr SocketAddress)
address <- IO (Ptr (Ptr SocketAddress))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (Ptr Gio.SocketAddress.SocketAddress))
[Ptr InputVector]
vectors' <- (InputVector -> IO (Ptr InputVector))
-> [InputVector] -> IO [Ptr InputVector]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM InputVector -> IO (Ptr InputVector)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [InputVector]
vectors
Ptr InputVector
vectors'' <- Int -> [Ptr InputVector] -> IO (Ptr InputVector)
forall a. Int -> [Ptr a] -> IO (Ptr a)
packBlockArray Int
16 [Ptr InputVector]
vectors'
Ptr (Ptr (Ptr SocketControlMessage))
messages <- IO (Ptr (Ptr (Ptr SocketControlMessage)))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (Ptr (Ptr Gio.SocketControlMessage.SocketControlMessage)))
Ptr Int32
numMessages <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
Ptr Int32
flags' <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Int32
flags' Int32
flags
Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just b
jCancellable -> do
Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
IO
(Int64, Maybe SocketAddress, Maybe [SocketControlMessage], Int32)
-> IO ()
-> IO
(Int64, Maybe SocketAddress, Maybe [SocketControlMessage], Int32)
forall a b. IO a -> IO b -> IO a
onException (do
Int64
result <- (Ptr (Ptr GError) -> IO Int64) -> IO Int64
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO Int64) -> IO Int64)
-> (Ptr (Ptr GError) -> IO Int64) -> IO Int64
forall a b. (a -> b) -> a -> b
$ Ptr Socket
-> Ptr (Ptr SocketAddress)
-> Ptr InputVector
-> Int32
-> Ptr (Ptr (Ptr SocketControlMessage))
-> Ptr Int32
-> Ptr Int32
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO Int64
g_socket_receive_message Ptr Socket
socket' Ptr (Ptr SocketAddress)
address Ptr InputVector
vectors'' Int32
numVectors Ptr (Ptr (Ptr SocketControlMessage))
messages Ptr Int32
numMessages Ptr Int32
flags' Ptr Cancellable
maybeCancellable
Int32
numMessages' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
numMessages
Ptr SocketAddress
address' <- Ptr (Ptr SocketAddress) -> IO (Ptr SocketAddress)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr SocketAddress)
address
Maybe SocketAddress
maybeAddress' <- Ptr SocketAddress
-> (Ptr SocketAddress -> IO SocketAddress)
-> IO (Maybe SocketAddress)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr SocketAddress
address' ((Ptr SocketAddress -> IO SocketAddress)
-> IO (Maybe SocketAddress))
-> (Ptr SocketAddress -> IO SocketAddress)
-> IO (Maybe SocketAddress)
forall a b. (a -> b) -> a -> b
$ \Ptr SocketAddress
address'' -> do
SocketAddress
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''
SocketAddress -> IO SocketAddress
forall (m :: * -> *) a. Monad m => a -> m a
return SocketAddress
address'''
Ptr (Ptr SocketControlMessage)
messages' <- Ptr (Ptr (Ptr SocketControlMessage))
-> IO (Ptr (Ptr SocketControlMessage))
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr (Ptr SocketControlMessage))
messages
Maybe [SocketControlMessage]
maybeMessages' <- Ptr (Ptr SocketControlMessage)
-> (Ptr (Ptr SocketControlMessage) -> IO [SocketControlMessage])
-> IO (Maybe [SocketControlMessage])
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr (Ptr SocketControlMessage)
messages' ((Ptr (Ptr SocketControlMessage) -> IO [SocketControlMessage])
-> IO (Maybe [SocketControlMessage]))
-> (Ptr (Ptr SocketControlMessage) -> IO [SocketControlMessage])
-> IO (Maybe [SocketControlMessage])
forall a b. (a -> b) -> a -> b
$ \Ptr (Ptr SocketControlMessage)
messages'' -> do
[Ptr SocketControlMessage]
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''
[SocketControlMessage]
messages'''' <- (Ptr SocketControlMessage -> IO SocketControlMessage)
-> [Ptr SocketControlMessage] -> IO [SocketControlMessage]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr SocketControlMessage -> SocketControlMessage)
-> Ptr SocketControlMessage -> IO SocketControlMessage
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr SocketControlMessage -> SocketControlMessage
Gio.SocketControlMessage.SocketControlMessage) [Ptr SocketControlMessage]
messages'''
Ptr (Ptr SocketControlMessage) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr SocketControlMessage)
messages''
[SocketControlMessage] -> IO [SocketControlMessage]
forall (m :: * -> *) a. Monad m => a -> m a
return [SocketControlMessage]
messages''''
Int32
flags'' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
flags'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
(InputVector -> IO ()) -> [InputVector] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ InputVector -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [InputVector]
vectors
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Ptr (Ptr SocketAddress) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr SocketAddress)
address
Ptr InputVector -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr InputVector
vectors''
Ptr (Ptr (Ptr SocketControlMessage)) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr (Ptr SocketControlMessage))
messages
Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
numMessages
Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
flags'
(Int64, Maybe SocketAddress, Maybe [SocketControlMessage], Int32)
-> IO
(Int64, Maybe SocketAddress, Maybe [SocketControlMessage], Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int64
result, Maybe SocketAddress
maybeAddress', Maybe [SocketControlMessage]
maybeMessages', Int32
flags'')
) (do
Ptr (Ptr SocketAddress) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr SocketAddress)
address
Ptr InputVector -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr InputVector
vectors''
Ptr (Ptr (Ptr SocketControlMessage)) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr (Ptr SocketControlMessage))
messages
Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
numMessages
Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
flags'
)
#if defined(ENABLE_OVERLOADING)
data SocketReceiveMessageMethodInfo
instance (signature ~ ([Gio.InputVector.InputVector] -> Int32 -> Maybe (b) -> m ((Int64, Maybe Gio.SocketAddress.SocketAddress, Maybe [Gio.SocketControlMessage.SocketControlMessage], Int32))), MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) => O.MethodInfo SocketReceiveMessageMethodInfo a signature where
overloadedMethod = socketReceiveMessage
#endif
foreign import ccall "g_socket_receive_messages" g_socket_receive_messages ::
Ptr Socket ->
Ptr Gio.InputMessage.InputMessage ->
Word32 ->
Int32 ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO Int32
socketReceiveMessages ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) =>
a
-> [Gio.InputMessage.InputMessage]
-> Int32
-> Maybe (b)
-> m Int32
socketReceiveMessages :: a -> [InputMessage] -> Int32 -> Maybe b -> m Int32
socketReceiveMessages a
socket [InputMessage]
messages Int32
flags Maybe b
cancellable = IO Int32 -> m Int32
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 (t :: * -> *) a. Foldable t => t a -> Int
P.length [InputMessage]
messages
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
[Ptr InputMessage]
messages' <- (InputMessage -> IO (Ptr InputMessage))
-> [InputMessage] -> IO [Ptr InputMessage]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM InputMessage -> IO (Ptr InputMessage)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [InputMessage]
messages
Ptr InputMessage
messages'' <- Int -> [Ptr InputMessage] -> IO (Ptr InputMessage)
forall a. Int -> [Ptr a] -> IO (Ptr a)
packBlockArray Int
56 [Ptr InputMessage]
messages'
Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just b
jCancellable -> do
Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
IO Int32 -> IO () -> IO Int32
forall a b. IO a -> IO b -> IO a
onException (do
Int32
result <- (Ptr (Ptr GError) -> IO Int32) -> IO Int32
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO Int32) -> IO Int32)
-> (Ptr (Ptr GError) -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ Ptr Socket
-> Ptr InputMessage
-> Word32
-> Int32
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO Int32
g_socket_receive_messages Ptr Socket
socket' Ptr InputMessage
messages'' Word32
numMessages Int32
flags Ptr Cancellable
maybeCancellable
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
(InputMessage -> IO ()) -> [InputMessage] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ InputMessage -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [InputMessage]
messages
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Ptr InputMessage -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr InputMessage
messages''
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
) (do
Ptr InputMessage -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr InputMessage
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.MethodInfo SocketReceiveMessagesMethodInfo a signature where
overloadedMethod = socketReceiveMessages
#endif
foreign import ccall "g_socket_receive_with_blocking" g_socket_receive_with_blocking ::
Ptr Socket ->
Ptr Word8 ->
Word64 ->
CInt ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO Int64
socketReceiveWithBlocking ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) =>
a
-> ByteString
-> Bool
-> Maybe (b)
-> m Int64
socketReceiveWithBlocking :: a -> ByteString -> Bool -> Maybe b -> m Int64
socketReceiveWithBlocking a
socket ByteString
buffer Bool
blocking Maybe b
cancellable = IO Int64 -> m Int64
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 :: Word64
size = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
buffer
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
Ptr Word8
buffer' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
buffer
let blocking' :: CInt
blocking' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
blocking
Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just b
jCancellable -> do
Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
IO Int64 -> IO () -> IO Int64
forall a b. IO a -> IO b -> IO a
onException (do
Int64
result <- (Ptr (Ptr GError) -> IO Int64) -> IO Int64
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO Int64) -> IO Int64)
-> (Ptr (Ptr GError) -> IO Int64) -> IO Int64
forall a b. (a -> b) -> a -> b
$ Ptr Socket
-> Ptr Word8
-> Word64
-> CInt
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO Int64
g_socket_receive_with_blocking Ptr Socket
socket' Ptr Word8
buffer' Word64
size CInt
blocking' Ptr Cancellable
maybeCancellable
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
buffer'
Int64 -> IO Int64
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
result
) (do
Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
buffer'
)
#if defined(ENABLE_OVERLOADING)
data SocketReceiveWithBlockingMethodInfo
instance (signature ~ (ByteString -> Bool -> Maybe (b) -> m Int64), MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) => O.MethodInfo SocketReceiveWithBlockingMethodInfo a signature where
overloadedMethod = socketReceiveWithBlocking
#endif
foreign import ccall "g_socket_send" g_socket_send ::
Ptr Socket ->
Ptr Word8 ->
Word64 ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO Int64
socketSend ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) =>
a
-> ByteString
-> Maybe (b)
-> m Int64
socketSend :: a -> ByteString -> Maybe b -> m Int64
socketSend a
socket ByteString
buffer Maybe b
cancellable = IO Int64 -> m Int64
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 :: Word64
size = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
buffer
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
Ptr Word8
buffer' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
buffer
Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just b
jCancellable -> do
Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
IO Int64 -> IO () -> IO Int64
forall a b. IO a -> IO b -> IO a
onException (do
Int64
result <- (Ptr (Ptr GError) -> IO Int64) -> IO Int64
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO Int64) -> IO Int64)
-> (Ptr (Ptr GError) -> IO Int64) -> IO Int64
forall a b. (a -> b) -> a -> b
$ Ptr Socket
-> Ptr Word8
-> Word64
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO Int64
g_socket_send Ptr Socket
socket' Ptr Word8
buffer' Word64
size Ptr Cancellable
maybeCancellable
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
buffer'
Int64 -> IO Int64
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
result
) (do
Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
buffer'
)
#if defined(ENABLE_OVERLOADING)
data SocketSendMethodInfo
instance (signature ~ (ByteString -> Maybe (b) -> m Int64), MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) => O.MethodInfo SocketSendMethodInfo a signature where
overloadedMethod = socketSend
#endif
foreign import ccall "g_socket_send_message" g_socket_send_message ::
Ptr Socket ->
Ptr Gio.SocketAddress.SocketAddress ->
Ptr Gio.OutputVector.OutputVector ->
Int32 ->
Ptr (Ptr Gio.SocketControlMessage.SocketControlMessage) ->
Int32 ->
Int32 ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO Int64
socketSendMessage ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.SocketAddress.IsSocketAddress b, Gio.Cancellable.IsCancellable c) =>
a
-> Maybe (b)
-> [Gio.OutputVector.OutputVector]
-> Maybe ([Gio.SocketControlMessage.SocketControlMessage])
-> Int32
-> Maybe (c)
-> m Int64
socketSendMessage :: 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 (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 (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 (t :: * -> *) a. Foldable t => t a -> Int
P.length [OutputVector]
vectors
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
Ptr SocketAddress
maybeAddress <- case Maybe b
address of
Maybe b
Nothing -> Ptr SocketAddress -> IO (Ptr SocketAddress)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr SocketAddress
forall a. Ptr a
nullPtr
Just b
jAddress -> do
Ptr SocketAddress
jAddress' <- b -> IO (Ptr SocketAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jAddress
Ptr SocketAddress -> IO (Ptr SocketAddress)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr SocketAddress
jAddress'
[Ptr OutputVector]
vectors' <- (OutputVector -> IO (Ptr OutputVector))
-> [OutputVector] -> IO [Ptr OutputVector]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM OutputVector -> IO (Ptr OutputVector)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [OutputVector]
vectors
Ptr OutputVector
vectors'' <- Int -> [Ptr OutputVector] -> IO (Ptr OutputVector)
forall a. Int -> [Ptr a] -> IO (Ptr a)
packBlockArray Int
16 [Ptr OutputVector]
vectors'
Ptr (Ptr SocketControlMessage)
maybeMessages <- case Maybe [SocketControlMessage]
messages of
Maybe [SocketControlMessage]
Nothing -> Ptr (Ptr SocketControlMessage)
-> IO (Ptr (Ptr SocketControlMessage))
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr (Ptr SocketControlMessage)
forall a. Ptr a
nullPtr
Just [SocketControlMessage]
jMessages -> do
[Ptr SocketControlMessage]
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)
mapM SocketControlMessage -> IO (Ptr SocketControlMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr [SocketControlMessage]
jMessages
Ptr (Ptr SocketControlMessage)
jMessages'' <- [Ptr SocketControlMessage] -> IO (Ptr (Ptr SocketControlMessage))
forall a. [Ptr a] -> IO (Ptr (Ptr a))
packPtrArray [Ptr SocketControlMessage]
jMessages'
Ptr (Ptr SocketControlMessage)
-> IO (Ptr (Ptr SocketControlMessage))
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr (Ptr SocketControlMessage)
jMessages''
Ptr Cancellable
maybeCancellable <- case Maybe c
cancellable of
Maybe c
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just c
jCancellable -> do
Ptr Cancellable
jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
IO Int64 -> IO () -> IO Int64
forall a b. IO a -> IO b -> IO a
onException (do
Int64
result <- (Ptr (Ptr GError) -> IO Int64) -> IO Int64
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO Int64) -> IO Int64)
-> (Ptr (Ptr GError) -> IO Int64) -> IO Int64
forall a b. (a -> b) -> a -> b
$ Ptr Socket
-> Ptr SocketAddress
-> Ptr OutputVector
-> Int32
-> Ptr (Ptr SocketControlMessage)
-> Int32
-> Int32
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO Int64
g_socket_send_message Ptr Socket
socket' Ptr SocketAddress
maybeAddress Ptr OutputVector
vectors'' Int32
numVectors Ptr (Ptr SocketControlMessage)
maybeMessages Int32
numMessages Int32
flags Ptr Cancellable
maybeCancellable
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
address b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
(OutputVector -> IO ()) -> [OutputVector] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ OutputVector -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [OutputVector]
vectors
Maybe [SocketControlMessage]
-> ([SocketControlMessage] -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe [SocketControlMessage]
messages ((SocketControlMessage -> IO ()) -> [SocketControlMessage] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ SocketControlMessage -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr)
Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
cancellable c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Ptr OutputVector -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr OutputVector
vectors''
Ptr (Ptr SocketControlMessage) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr SocketControlMessage)
maybeMessages
Int64 -> IO Int64
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
result
) (do
Ptr OutputVector -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr OutputVector
vectors''
Ptr (Ptr SocketControlMessage) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr SocketControlMessage)
maybeMessages
)
#if defined(ENABLE_OVERLOADING)
data SocketSendMessageMethodInfo
instance (signature ~ (Maybe (b) -> [Gio.OutputVector.OutputVector] -> Maybe ([Gio.SocketControlMessage.SocketControlMessage]) -> Int32 -> Maybe (c) -> m Int64), MonadIO m, IsSocket a, Gio.SocketAddress.IsSocketAddress b, Gio.Cancellable.IsCancellable c) => O.MethodInfo SocketSendMessageMethodInfo a signature where
overloadedMethod = socketSendMessage
#endif
foreign import ccall "g_socket_send_message_with_timeout" g_socket_send_message_with_timeout ::
Ptr Socket ->
Ptr Gio.SocketAddress.SocketAddress ->
Ptr Gio.OutputVector.OutputVector ->
Int32 ->
Ptr (Ptr Gio.SocketControlMessage.SocketControlMessage) ->
Int32 ->
Int32 ->
Int64 ->
Ptr Word64 ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO CInt
socketSendMessageWithTimeout ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.SocketAddress.IsSocketAddress b, Gio.Cancellable.IsCancellable c) =>
a
-> Maybe (b)
-> [Gio.OutputVector.OutputVector]
-> Maybe ([Gio.SocketControlMessage.SocketControlMessage])
-> Int32
-> Int64
-> Maybe (c)
-> m ((Gio.Enums.PollableReturn, Word64))
socketSendMessageWithTimeout :: a
-> Maybe b
-> [OutputVector]
-> Maybe [SocketControlMessage]
-> Int32
-> Int64
-> Maybe c
-> m (PollableReturn, Word64)
socketSendMessageWithTimeout a
socket Maybe b
address [OutputVector]
vectors Maybe [SocketControlMessage]
messages Int32
flags Int64
timeoutUs Maybe c
cancellable = IO (PollableReturn, Word64) -> m (PollableReturn, Word64)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (PollableReturn, Word64) -> m (PollableReturn, Word64))
-> IO (PollableReturn, Word64) -> m (PollableReturn, Word64)
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 (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 (t :: * -> *) a. Foldable t => t a -> Int
P.length [OutputVector]
vectors
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
Ptr SocketAddress
maybeAddress <- case Maybe b
address of
Maybe b
Nothing -> Ptr SocketAddress -> IO (Ptr SocketAddress)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr SocketAddress
forall a. Ptr a
nullPtr
Just b
jAddress -> do
Ptr SocketAddress
jAddress' <- b -> IO (Ptr SocketAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jAddress
Ptr SocketAddress -> IO (Ptr SocketAddress)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr SocketAddress
jAddress'
[Ptr OutputVector]
vectors' <- (OutputVector -> IO (Ptr OutputVector))
-> [OutputVector] -> IO [Ptr OutputVector]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM OutputVector -> IO (Ptr OutputVector)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [OutputVector]
vectors
Ptr OutputVector
vectors'' <- Int -> [Ptr OutputVector] -> IO (Ptr OutputVector)
forall a. Int -> [Ptr a] -> IO (Ptr a)
packBlockArray Int
16 [Ptr OutputVector]
vectors'
Ptr (Ptr SocketControlMessage)
maybeMessages <- case Maybe [SocketControlMessage]
messages of
Maybe [SocketControlMessage]
Nothing -> Ptr (Ptr SocketControlMessage)
-> IO (Ptr (Ptr SocketControlMessage))
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr (Ptr SocketControlMessage)
forall a. Ptr a
nullPtr
Just [SocketControlMessage]
jMessages -> do
[Ptr SocketControlMessage]
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)
mapM SocketControlMessage -> IO (Ptr SocketControlMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr [SocketControlMessage]
jMessages
Ptr (Ptr SocketControlMessage)
jMessages'' <- [Ptr SocketControlMessage] -> IO (Ptr (Ptr SocketControlMessage))
forall a. [Ptr a] -> IO (Ptr (Ptr a))
packPtrArray [Ptr SocketControlMessage]
jMessages'
Ptr (Ptr SocketControlMessage)
-> IO (Ptr (Ptr SocketControlMessage))
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr (Ptr SocketControlMessage)
jMessages''
Ptr Word64
bytesWritten <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
Ptr Cancellable
maybeCancellable <- case Maybe c
cancellable of
Maybe c
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just c
jCancellable -> do
Ptr Cancellable
jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
IO (PollableReturn, Word64) -> IO () -> IO (PollableReturn, Word64)
forall a b. IO a -> IO b -> IO a
onException (do
CInt
result <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Socket
-> Ptr SocketAddress
-> Ptr OutputVector
-> Int32
-> Ptr (Ptr SocketControlMessage)
-> Int32
-> Int32
-> Int64
-> Ptr Word64
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO CInt
g_socket_send_message_with_timeout Ptr Socket
socket' Ptr SocketAddress
maybeAddress Ptr OutputVector
vectors'' Int32
numVectors Ptr (Ptr SocketControlMessage)
maybeMessages Int32
numMessages Int32
flags Int64
timeoutUs Ptr Word64
bytesWritten Ptr Cancellable
maybeCancellable
let result' :: PollableReturn
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
Word64
bytesWritten' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
bytesWritten
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
address b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
(OutputVector -> IO ()) -> [OutputVector] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ OutputVector -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [OutputVector]
vectors
Maybe [SocketControlMessage]
-> ([SocketControlMessage] -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe [SocketControlMessage]
messages ((SocketControlMessage -> IO ()) -> [SocketControlMessage] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ SocketControlMessage -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr)
Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
cancellable c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Ptr OutputVector -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr OutputVector
vectors''
Ptr (Ptr SocketControlMessage) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr SocketControlMessage)
maybeMessages
Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
bytesWritten
(PollableReturn, Word64) -> IO (PollableReturn, Word64)
forall (m :: * -> *) a. Monad m => a -> m a
return (PollableReturn
result', Word64
bytesWritten')
) (do
Ptr OutputVector -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr OutputVector
vectors''
Ptr (Ptr SocketControlMessage) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr SocketControlMessage)
maybeMessages
Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
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, Word64))), MonadIO m, IsSocket a, Gio.SocketAddress.IsSocketAddress b, Gio.Cancellable.IsCancellable c) => O.MethodInfo SocketSendMessageWithTimeoutMethodInfo a signature where
overloadedMethod = socketSendMessageWithTimeout
#endif
foreign import ccall "g_socket_send_messages" g_socket_send_messages ::
Ptr Socket ->
Ptr Gio.OutputMessage.OutputMessage ->
Word32 ->
Int32 ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO Int32
socketSendMessages ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) =>
a
-> [Gio.OutputMessage.OutputMessage]
-> Int32
-> Maybe (b)
-> m Int32
socketSendMessages :: a -> [OutputMessage] -> Int32 -> Maybe b -> m Int32
socketSendMessages a
socket [OutputMessage]
messages Int32
flags Maybe b
cancellable = IO Int32 -> m Int32
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 (t :: * -> *) a. Foldable t => t a -> Int
P.length [OutputMessage]
messages
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
[Ptr OutputMessage]
messages' <- (OutputMessage -> IO (Ptr OutputMessage))
-> [OutputMessage] -> IO [Ptr OutputMessage]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM OutputMessage -> IO (Ptr OutputMessage)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [OutputMessage]
messages
Ptr OutputMessage
messages'' <- Int -> [Ptr OutputMessage] -> IO (Ptr OutputMessage)
forall a. Int -> [Ptr a] -> IO (Ptr a)
packBlockArray Int
40 [Ptr OutputMessage]
messages'
Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just b
jCancellable -> do
Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
IO Int32 -> IO () -> IO Int32
forall a b. IO a -> IO b -> IO a
onException (do
Int32
result <- (Ptr (Ptr GError) -> IO Int32) -> IO Int32
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO Int32) -> IO Int32)
-> (Ptr (Ptr GError) -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ Ptr Socket
-> Ptr OutputMessage
-> Word32
-> Int32
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO Int32
g_socket_send_messages Ptr Socket
socket' Ptr OutputMessage
messages'' Word32
numMessages Int32
flags Ptr Cancellable
maybeCancellable
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
(OutputMessage -> IO ()) -> [OutputMessage] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ OutputMessage -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [OutputMessage]
messages
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Ptr OutputMessage -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr OutputMessage
messages''
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
) (do
Ptr OutputMessage -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr OutputMessage
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.MethodInfo SocketSendMessagesMethodInfo a signature where
overloadedMethod = socketSendMessages
#endif
foreign import ccall "g_socket_send_to" g_socket_send_to ::
Ptr Socket ->
Ptr Gio.SocketAddress.SocketAddress ->
Ptr Word8 ->
Word64 ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO Int64
socketSendTo ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.SocketAddress.IsSocketAddress b, Gio.Cancellable.IsCancellable c) =>
a
-> Maybe (b)
-> ByteString
-> Maybe (c)
-> m Int64
socketSendTo :: a -> Maybe b -> ByteString -> Maybe c -> m Int64
socketSendTo a
socket Maybe b
address ByteString
buffer Maybe c
cancellable = IO Int64 -> m Int64
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 :: Word64
size = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
buffer
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
Ptr SocketAddress
maybeAddress <- case Maybe b
address of
Maybe b
Nothing -> Ptr SocketAddress -> IO (Ptr SocketAddress)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr SocketAddress
forall a. Ptr a
nullPtr
Just b
jAddress -> do
Ptr SocketAddress
jAddress' <- b -> IO (Ptr SocketAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jAddress
Ptr SocketAddress -> IO (Ptr SocketAddress)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr SocketAddress
jAddress'
Ptr Word8
buffer' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
buffer
Ptr Cancellable
maybeCancellable <- case Maybe c
cancellable of
Maybe c
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just c
jCancellable -> do
Ptr Cancellable
jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
IO Int64 -> IO () -> IO Int64
forall a b. IO a -> IO b -> IO a
onException (do
Int64
result <- (Ptr (Ptr GError) -> IO Int64) -> IO Int64
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO Int64) -> IO Int64)
-> (Ptr (Ptr GError) -> IO Int64) -> IO Int64
forall a b. (a -> b) -> a -> b
$ Ptr Socket
-> Ptr SocketAddress
-> Ptr Word8
-> Word64
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO Int64
g_socket_send_to Ptr Socket
socket' Ptr SocketAddress
maybeAddress Ptr Word8
buffer' Word64
size Ptr Cancellable
maybeCancellable
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
address b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
cancellable c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
buffer'
Int64 -> IO Int64
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
result
) (do
Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
buffer'
)
#if defined(ENABLE_OVERLOADING)
data SocketSendToMethodInfo
instance (signature ~ (Maybe (b) -> ByteString -> Maybe (c) -> m Int64), MonadIO m, IsSocket a, Gio.SocketAddress.IsSocketAddress b, Gio.Cancellable.IsCancellable c) => O.MethodInfo SocketSendToMethodInfo a signature where
overloadedMethod = socketSendTo
#endif
foreign import ccall "g_socket_send_with_blocking" g_socket_send_with_blocking ::
Ptr Socket ->
Ptr Word8 ->
Word64 ->
CInt ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO Int64
socketSendWithBlocking ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) =>
a
-> ByteString
-> Bool
-> Maybe (b)
-> m Int64
socketSendWithBlocking :: a -> ByteString -> Bool -> Maybe b -> m Int64
socketSendWithBlocking a
socket ByteString
buffer Bool
blocking Maybe b
cancellable = IO Int64 -> m Int64
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 :: Word64
size = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
buffer
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
Ptr Word8
buffer' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
buffer
let blocking' :: CInt
blocking' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
blocking
Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just b
jCancellable -> do
Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
IO Int64 -> IO () -> IO Int64
forall a b. IO a -> IO b -> IO a
onException (do
Int64
result <- (Ptr (Ptr GError) -> IO Int64) -> IO Int64
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO Int64) -> IO Int64)
-> (Ptr (Ptr GError) -> IO Int64) -> IO Int64
forall a b. (a -> b) -> a -> b
$ Ptr Socket
-> Ptr Word8
-> Word64
-> CInt
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO Int64
g_socket_send_with_blocking Ptr Socket
socket' Ptr Word8
buffer' Word64
size CInt
blocking' Ptr Cancellable
maybeCancellable
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
buffer'
Int64 -> IO Int64
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
result
) (do
Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
buffer'
)
#if defined(ENABLE_OVERLOADING)
data SocketSendWithBlockingMethodInfo
instance (signature ~ (ByteString -> Bool -> Maybe (b) -> m Int64), MonadIO m, IsSocket a, Gio.Cancellable.IsCancellable b) => O.MethodInfo SocketSendWithBlockingMethodInfo a signature where
overloadedMethod = socketSendWithBlocking
#endif
foreign import ccall "g_socket_set_blocking" g_socket_set_blocking ::
Ptr Socket ->
CInt ->
IO ()
socketSetBlocking ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> Bool
-> m ()
socketSetBlocking :: a -> Bool -> m ()
socketSetBlocking a
socket Bool
blocking = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
let blocking' :: CInt
blocking' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
blocking
Ptr Socket -> CInt -> IO ()
g_socket_set_blocking Ptr Socket
socket' CInt
blocking'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SocketSetBlockingMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsSocket a) => O.MethodInfo SocketSetBlockingMethodInfo a signature where
overloadedMethod = socketSetBlocking
#endif
foreign import ccall "g_socket_set_broadcast" g_socket_set_broadcast ::
Ptr Socket ->
CInt ->
IO ()
socketSetBroadcast ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> Bool
-> m ()
socketSetBroadcast :: a -> Bool -> m ()
socketSetBroadcast a
socket Bool
broadcast = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
let broadcast' :: CInt
broadcast' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
broadcast
Ptr Socket -> CInt -> IO ()
g_socket_set_broadcast Ptr Socket
socket' CInt
broadcast'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SocketSetBroadcastMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsSocket a) => O.MethodInfo SocketSetBroadcastMethodInfo a signature where
overloadedMethod = socketSetBroadcast
#endif
foreign import ccall "g_socket_set_keepalive" g_socket_set_keepalive ::
Ptr Socket ->
CInt ->
IO ()
socketSetKeepalive ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> Bool
-> m ()
socketSetKeepalive :: a -> Bool -> m ()
socketSetKeepalive a
socket Bool
keepalive = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
let keepalive' :: CInt
keepalive' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
keepalive
Ptr Socket -> CInt -> IO ()
g_socket_set_keepalive Ptr Socket
socket' CInt
keepalive'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SocketSetKeepaliveMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsSocket a) => O.MethodInfo SocketSetKeepaliveMethodInfo a signature where
overloadedMethod = socketSetKeepalive
#endif
foreign import ccall "g_socket_set_listen_backlog" g_socket_set_listen_backlog ::
Ptr Socket ->
Int32 ->
IO ()
socketSetListenBacklog ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> Int32
-> m ()
socketSetListenBacklog :: a -> Int32 -> m ()
socketSetListenBacklog a
socket Int32
backlog = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
Ptr Socket -> Int32 -> IO ()
g_socket_set_listen_backlog Ptr Socket
socket' Int32
backlog
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SocketSetListenBacklogMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsSocket a) => O.MethodInfo SocketSetListenBacklogMethodInfo a signature where
overloadedMethod = socketSetListenBacklog
#endif
foreign import ccall "g_socket_set_multicast_loopback" g_socket_set_multicast_loopback ::
Ptr Socket ->
CInt ->
IO ()
socketSetMulticastLoopback ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> Bool
-> m ()
socketSetMulticastLoopback :: a -> Bool -> m ()
socketSetMulticastLoopback a
socket Bool
loopback = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
let loopback' :: CInt
loopback' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
loopback
Ptr Socket -> CInt -> IO ()
g_socket_set_multicast_loopback Ptr Socket
socket' CInt
loopback'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SocketSetMulticastLoopbackMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsSocket a) => O.MethodInfo SocketSetMulticastLoopbackMethodInfo a signature where
overloadedMethod = socketSetMulticastLoopback
#endif
foreign import ccall "g_socket_set_multicast_ttl" g_socket_set_multicast_ttl ::
Ptr Socket ->
Word32 ->
IO ()
socketSetMulticastTtl ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> Word32
-> m ()
socketSetMulticastTtl :: a -> Word32 -> m ()
socketSetMulticastTtl a
socket Word32
ttl = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
Ptr Socket -> Word32 -> IO ()
g_socket_set_multicast_ttl Ptr Socket
socket' Word32
ttl
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SocketSetMulticastTtlMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsSocket a) => O.MethodInfo SocketSetMulticastTtlMethodInfo a signature where
overloadedMethod = socketSetMulticastTtl
#endif
foreign import ccall "g_socket_set_option" g_socket_set_option ::
Ptr Socket ->
Int32 ->
Int32 ->
Int32 ->
Ptr (Ptr GError) ->
IO CInt
socketSetOption ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> Int32
-> Int32
-> Int32
-> m ()
socketSetOption :: a -> Int32 -> Int32 -> Int32 -> m ()
socketSetOption a
socket Int32
level Int32
optname Int32
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Socket
-> Int32 -> Int32 -> Int32 -> Ptr (Ptr GError) -> IO CInt
g_socket_set_option Ptr Socket
socket' Int32
level Int32
optname Int32
value
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data SocketSetOptionMethodInfo
instance (signature ~ (Int32 -> Int32 -> Int32 -> m ()), MonadIO m, IsSocket a) => O.MethodInfo SocketSetOptionMethodInfo a signature where
overloadedMethod = socketSetOption
#endif
foreign import ccall "g_socket_set_timeout" g_socket_set_timeout ::
Ptr Socket ->
Word32 ->
IO ()
socketSetTimeout ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> Word32
-> m ()
socketSetTimeout :: a -> Word32 -> m ()
socketSetTimeout a
socket Word32
timeout = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
Ptr Socket -> Word32 -> IO ()
g_socket_set_timeout Ptr Socket
socket' Word32
timeout
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SocketSetTimeoutMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsSocket a) => O.MethodInfo SocketSetTimeoutMethodInfo a signature where
overloadedMethod = socketSetTimeout
#endif
foreign import ccall "g_socket_set_ttl" g_socket_set_ttl ::
Ptr Socket ->
Word32 ->
IO ()
socketSetTtl ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> Word32
-> m ()
socketSetTtl :: a -> Word32 -> m ()
socketSetTtl a
socket Word32
ttl = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
Ptr Socket -> Word32 -> IO ()
g_socket_set_ttl Ptr Socket
socket' Word32
ttl
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SocketSetTtlMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsSocket a) => O.MethodInfo SocketSetTtlMethodInfo a signature where
overloadedMethod = socketSetTtl
#endif
foreign import ccall "g_socket_shutdown" g_socket_shutdown ::
Ptr Socket ->
CInt ->
CInt ->
Ptr (Ptr GError) ->
IO CInt
socketShutdown ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> Bool
-> Bool
-> m ()
socketShutdown :: a -> Bool -> Bool -> m ()
socketShutdown a
socket Bool
shutdownRead Bool
shutdownWrite = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
let shutdownRead' :: CInt
shutdownRead' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
shutdownRead
let shutdownWrite' :: CInt
shutdownWrite' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
shutdownWrite
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Socket -> CInt -> CInt -> Ptr (Ptr GError) -> IO CInt
g_socket_shutdown Ptr Socket
socket' CInt
shutdownRead' CInt
shutdownWrite'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data SocketShutdownMethodInfo
instance (signature ~ (Bool -> Bool -> m ()), MonadIO m, IsSocket a) => O.MethodInfo SocketShutdownMethodInfo a signature where
overloadedMethod = socketShutdown
#endif
foreign import ccall "g_socket_speaks_ipv4" g_socket_speaks_ipv4 ::
Ptr Socket ->
IO CInt
socketSpeaksIpv4 ::
(B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
a
-> m Bool
socketSpeaksIpv4 :: a -> m Bool
socketSpeaksIpv4 a
socket = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Socket
socket' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket
CInt
result <- Ptr Socket -> IO CInt
g_socket_speaks_ipv4 Ptr Socket
socket'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data SocketSpeaksIpv4MethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSocket a) => O.MethodInfo SocketSpeaksIpv4MethodInfo a signature where
overloadedMethod = socketSpeaksIpv4
#endif