gi-soup-2.4.11: Libsoup bindings

CopyrightWill Thompson, Iñaki García Etxebarria and Jonas Platte
LicenseLGPL-2.1
MaintainerIñaki García Etxebarria (garetxe@gmail.com)
Safe HaskellNone
LanguageHaskell2010

GI.Soup.Objects.Socket

Contents

Description

 

Synopsis

Exported types

newtype Socket Source #

Constructors

Socket (ManagedPtr Socket) 

Instances

GObject Socket Source # 

Methods

gobjectType :: Socket -> IO GType #

IsInitable Socket Source # 
IsObject Socket Source # 
IsSocket Socket Source # 
((~) * info (ResolveSocketMethod t Socket), MethodInfo * info Socket p) => IsLabel t (Socket -> p) Source # 

Methods

fromLabel :: Proxy# Symbol t -> Socket -> p #

((~) * info (ResolveSocketMethod t Socket), MethodInfo * info Socket p) => IsLabelProxy t (Socket -> p) Source # 

Methods

fromLabelProxy :: Proxy Symbol t -> Socket -> p #

HasAttributeList * Socket Source # 
type AttributeList Socket Source # 
type SignalList Socket Source # 

Methods

connectAsync

socketConnectAsync Source #

Arguments

:: (HasCallStack, MonadIO m, IsSocket a, IsCancellable b) 
=> a

sock: a client Socket (which must not already be connected)

-> Maybe b

cancellable: a Cancellable, or Nothing

-> SocketCallback

callback: callback to call after connecting

-> m () 

Begins asynchronously connecting to sock's remote address. The socket will call callback when it succeeds or fails (but not before returning from this function).

If cancellable is non-Nothing, it can be used to cancel the connection. callback will still be invoked in this case, with a status of StatusCancelled.

connectSync

socketConnectSync Source #

Arguments

:: (HasCallStack, MonadIO m, IsSocket a, IsCancellable b) 
=> a

sock: a client Socket (which must not already be connected)

-> Maybe b

cancellable: a Cancellable, or Nothing

-> m Word32

Returns: a success or failure code.

Attempt to synchronously connect sock to its remote address.

If cancellable is non-Nothing, it can be used to cancel the connection, in which case socketConnectSync will return StatusCancelled.

disconnect

data SocketDisconnectMethodInfo Source #

Instances

((~) * signature (m ()), MonadIO m, IsSocket a) => MethodInfo * SocketDisconnectMethodInfo a signature Source # 

socketDisconnect Source #

Arguments

:: (HasCallStack, MonadIO m, IsSocket a) 
=> a

sock: a Socket

-> m () 

Disconnects sock. Any further read or write attempts on it will fail.

getFd

data SocketGetFdMethodInfo Source #

Instances

((~) * signature (m Int32), MonadIO m, IsSocket a) => MethodInfo * SocketGetFdMethodInfo a signature Source # 

Methods

overloadedMethod :: MethodProxy SocketGetFdMethodInfo a -> signature -> s #

socketGetFd Source #

Arguments

:: (HasCallStack, MonadIO m, IsSocket a) 
=> a

sock: a Socket

-> m Int32

Returns: sock's file descriptor.

Gets sock's underlying file descriptor.

Note that fiddling with the file descriptor may break the Socket.

getLocalAddress

socketGetLocalAddress Source #

Arguments

:: (HasCallStack, MonadIO m, IsSocket a) 
=> a

sock: a Socket

-> m Address

Returns: the Address

Returns the Address corresponding to the local end of sock.

Calling this method on an unconnected socket is considered to be an error, and produces undefined results.

getRemoteAddress

socketGetRemoteAddress Source #

Arguments

:: (HasCallStack, MonadIO m, IsSocket a) 
=> a

sock: a Socket

-> m Address

Returns: the Address

Returns the Address corresponding to the remote end of sock.

Calling this method on an unconnected socket is considered to be an error, and produces undefined results.

isConnected

socketIsConnected Source #

Arguments

:: (HasCallStack, MonadIO m, IsSocket a) 
=> a

sock: a Socket

-> m Bool

Returns: True or False.

Tests if sock is connected to another host

isSsl

data SocketIsSslMethodInfo Source #

Instances

((~) * signature (m Bool), MonadIO m, IsSocket a) => MethodInfo * SocketIsSslMethodInfo a signature Source # 

Methods

overloadedMethod :: MethodProxy SocketIsSslMethodInfo a -> signature -> s #

socketIsSsl Source #

Arguments

:: (HasCallStack, MonadIO m, IsSocket a) 
=> a

sock: a Socket

-> m Bool

Returns: True if sock has SSL credentials set

Tests if sock is doing (or has attempted to do) SSL.

listen

data SocketListenMethodInfo Source #

Instances

((~) * signature (m Bool), MonadIO m, IsSocket a) => MethodInfo * SocketListenMethodInfo a signature Source # 

socketListen Source #

Arguments

:: (HasCallStack, MonadIO m, IsSocket a) 
=> a

sock: a server Socket (which must not already be connected or listening)

-> m Bool

Returns: whether or not sock is now listening.

Makes sock start listening on its local address. When connections come in, sock will emit Socket::new_connection.

read

data SocketReadMethodInfo Source #

Instances

((~) * signature (ByteString -> Maybe b -> m (SocketIOStatus, Word64)), MonadIO m, IsSocket a, IsCancellable b) => MethodInfo * SocketReadMethodInfo a signature Source # 

Methods

overloadedMethod :: MethodProxy SocketReadMethodInfo a -> signature -> s #

socketRead Source #

Arguments

:: (HasCallStack, MonadIO m, IsSocket a, IsCancellable b) 
=> a

sock: the socket

-> ByteString

buffer: buffer to read into

-> Maybe b

cancellable: a Cancellable, or Nothing

-> m (SocketIOStatus, Word64)

Returns: a SocketIOStatus, as described above (or SocketIOStatusEof if the socket is no longer connected, or SocketIOStatusError on any other error, in which case error will also be set). (Can throw GError)

Attempts to read up to len bytes from sock into buffer. If some data is successfully read, socketRead will return SocketIOStatusOk, and *nread will contain the number of bytes actually read (which may be less than len).

If sock is non-blocking, and no data is available, the return value will be SocketIOStatusWouldBlock. In this case, the caller can connect to the Socket::readable signal to know when there is more data to read. (NB: You MUST read all available data off the socket first. Socket::readable is only emitted after socketRead returns SocketIOStatusWouldBlock, and it is only emitted once. See the documentation for Socket:non-blocking.)

readUntil

socketReadUntil Source #

Arguments

:: (HasCallStack, MonadIO m, IsSocket a, IsCancellable b) 
=> a

sock: the socket

-> ByteString

buffer: buffer to read into

-> Ptr ()

boundary: boundary to read until

-> Word64

boundaryLen: length of boundary in bytes

-> Bool

gotBoundary: on return, whether or not the data in buffer ends with the boundary string

-> Maybe b

cancellable: a Cancellable, or Nothing

-> m (SocketIOStatus, Word64)

Returns: as for socketRead (Can throw GError)

Like socketRead, but reads no further than the first occurrence of boundary. (If the boundary is found, it will be included in the returned data, and *gotBoundary will be set to True.) Any data after the boundary will returned in future reads.

socketReadUntil will almost always return fewer than len bytes: if the boundary is found, then it will only return the bytes up until the end of the boundary, and if the boundary is not found, then it will leave the last <literal>(boundary_len - 1)</literal> bytes in its internal buffer, in case they form the start of the boundary string. Thus, len normally needs to be at least 1 byte longer than boundaryLen if you want to make any progress at all.

startProxySsl

socketStartProxySsl Source #

Arguments

:: (HasCallStack, MonadIO m, IsSocket a, IsCancellable b) 
=> a

sock: the socket

-> Text

sslHost: hostname of the SSL server

-> Maybe b

cancellable: a Cancellable

-> m Bool

Returns: success or failure

Starts using SSL on socket, expecting to find a host named sslHost.

startSsl

data SocketStartSslMethodInfo Source #

Instances

((~) * signature (Maybe b -> m Bool), MonadIO m, IsSocket a, IsCancellable b) => MethodInfo * SocketStartSslMethodInfo a signature Source # 

socketStartSsl Source #

Arguments

:: (HasCallStack, MonadIO m, IsSocket a, IsCancellable b) 
=> a

sock: the socket

-> Maybe b

cancellable: a Cancellable

-> m Bool

Returns: success or failure

Starts using SSL on socket.

write

socketWrite Source #

Arguments

:: (HasCallStack, MonadIO m, IsSocket a, IsCancellable b) 
=> a

sock: the socket

-> ByteString

buffer: data to write

-> Maybe b

cancellable: a Cancellable, or Nothing

-> m (SocketIOStatus, Word64)

Returns: a SocketIOStatus, as described above (or SocketIOStatusEof or SocketIOStatusError. error will be set if the return value is SocketIOStatusError.) (Can throw GError)

Attempts to write len bytes from buffer to sock. If some data is successfully written, the return status will be SocketIOStatusOk, and *nwrote will contain the number of bytes actually written (which may be less than len).

If sock is non-blocking, and no data could be written right away, the return value will be SocketIOStatusWouldBlock. In this case, the caller can connect to the Socket::writable signal to know when more data can be written. (NB: Socket::writable is only emitted after socketWrite returns SocketIOStatusWouldBlock, and it is only emitted once. See the documentation for Socket:non-blocking.)

Properties

asyncContext

data SocketAsyncContextPropertyInfo Source #

Instances

AttrInfo SocketAsyncContextPropertyInfo Source # 
type AttrOrigin SocketAsyncContextPropertyInfo Source # 
type AttrLabel SocketAsyncContextPropertyInfo Source # 
type AttrGetType SocketAsyncContextPropertyInfo Source # 
type AttrBaseTypeConstraint SocketAsyncContextPropertyInfo Source # 
type AttrSetTypeConstraint SocketAsyncContextPropertyInfo Source # 
type AttrAllowedOps SocketAsyncContextPropertyInfo Source # 

fd

data SocketFdPropertyInfo Source #

Instances

AttrInfo SocketFdPropertyInfo Source # 
type AttrOrigin SocketFdPropertyInfo Source # 
type AttrLabel SocketFdPropertyInfo Source # 
type AttrGetType SocketFdPropertyInfo Source # 
type AttrBaseTypeConstraint SocketFdPropertyInfo Source # 
type AttrSetTypeConstraint SocketFdPropertyInfo Source # 
type AttrAllowedOps SocketFdPropertyInfo Source # 

gsocket

data SocketGsocketPropertyInfo Source #

Instances

AttrInfo SocketGsocketPropertyInfo Source # 
type AttrOrigin SocketGsocketPropertyInfo Source # 
type AttrLabel SocketGsocketPropertyInfo Source # 
type AttrGetType SocketGsocketPropertyInfo Source # 
type AttrBaseTypeConstraint SocketGsocketPropertyInfo Source # 
type AttrSetTypeConstraint SocketGsocketPropertyInfo Source # 
type AttrAllowedOps SocketGsocketPropertyInfo Source # 

iostream

data SocketIostreamPropertyInfo Source #

Instances

AttrInfo SocketIostreamPropertyInfo Source # 
type AttrOrigin SocketIostreamPropertyInfo Source # 
type AttrLabel SocketIostreamPropertyInfo Source # 
type AttrGetType SocketIostreamPropertyInfo Source # 
type AttrBaseTypeConstraint SocketIostreamPropertyInfo Source # 
type AttrSetTypeConstraint SocketIostreamPropertyInfo Source # 
type AttrAllowedOps SocketIostreamPropertyInfo Source # 

ipv6Only

data SocketIpv6OnlyPropertyInfo Source #

Instances

AttrInfo SocketIpv6OnlyPropertyInfo Source # 
type AttrOrigin SocketIpv6OnlyPropertyInfo Source # 
type AttrLabel SocketIpv6OnlyPropertyInfo Source # 
type AttrGetType SocketIpv6OnlyPropertyInfo Source # 
type AttrBaseTypeConstraint SocketIpv6OnlyPropertyInfo Source # 
type AttrSetTypeConstraint SocketIpv6OnlyPropertyInfo Source # 
type AttrAllowedOps SocketIpv6OnlyPropertyInfo Source # 

setSocketIpv6Only :: (MonadIO m, IsSocket o) => o -> Bool -> m () Source #

isServer

data SocketIsServerPropertyInfo Source #

Instances

AttrInfo SocketIsServerPropertyInfo Source # 
type AttrOrigin SocketIsServerPropertyInfo Source # 
type AttrLabel SocketIsServerPropertyInfo Source # 
type AttrGetType SocketIsServerPropertyInfo Source # 
type AttrBaseTypeConstraint SocketIsServerPropertyInfo Source # 
type AttrSetTypeConstraint SocketIsServerPropertyInfo Source # 
type AttrAllowedOps SocketIsServerPropertyInfo Source # 

localAddress

data SocketLocalAddressPropertyInfo Source #

Instances

AttrInfo SocketLocalAddressPropertyInfo Source # 
type AttrOrigin SocketLocalAddressPropertyInfo Source # 
type AttrLabel SocketLocalAddressPropertyInfo Source # 
type AttrGetType SocketLocalAddressPropertyInfo Source # 
type AttrBaseTypeConstraint SocketLocalAddressPropertyInfo Source # 
type AttrSetTypeConstraint SocketLocalAddressPropertyInfo Source # 
type AttrAllowedOps SocketLocalAddressPropertyInfo Source # 

nonBlocking

data SocketNonBlockingPropertyInfo Source #

Instances

AttrInfo SocketNonBlockingPropertyInfo Source # 
type AttrOrigin SocketNonBlockingPropertyInfo Source # 
type AttrLabel SocketNonBlockingPropertyInfo Source # 
type AttrGetType SocketNonBlockingPropertyInfo Source # 
type AttrBaseTypeConstraint SocketNonBlockingPropertyInfo Source # 
type AttrSetTypeConstraint SocketNonBlockingPropertyInfo Source # 
type AttrAllowedOps SocketNonBlockingPropertyInfo Source # 

setSocketNonBlocking :: (MonadIO m, IsSocket o) => o -> Bool -> m () Source #

remoteAddress

data SocketRemoteAddressPropertyInfo Source #

Instances

AttrInfo SocketRemoteAddressPropertyInfo Source # 
type AttrOrigin SocketRemoteAddressPropertyInfo Source # 
type AttrLabel SocketRemoteAddressPropertyInfo Source # 
type AttrGetType SocketRemoteAddressPropertyInfo Source # 
type AttrBaseTypeConstraint SocketRemoteAddressPropertyInfo Source # 
type AttrSetTypeConstraint SocketRemoteAddressPropertyInfo Source # 
type AttrAllowedOps SocketRemoteAddressPropertyInfo Source # 

sslCreds

data SocketSslCredsPropertyInfo Source #

Instances

AttrInfo SocketSslCredsPropertyInfo Source # 
type AttrOrigin SocketSslCredsPropertyInfo Source # 
type AttrLabel SocketSslCredsPropertyInfo Source # 
type AttrGetType SocketSslCredsPropertyInfo Source # 
type AttrBaseTypeConstraint SocketSslCredsPropertyInfo Source # 
type AttrSetTypeConstraint SocketSslCredsPropertyInfo Source # 
type AttrAllowedOps SocketSslCredsPropertyInfo Source # 

getSocketSslCreds :: (MonadIO m, IsSocket o) => o -> m (Ptr ()) Source #

setSocketSslCreds :: (MonadIO m, IsSocket o) => o -> Ptr () -> m () Source #

sslFallback

data SocketSslFallbackPropertyInfo Source #

Instances

AttrInfo SocketSslFallbackPropertyInfo Source # 
type AttrOrigin SocketSslFallbackPropertyInfo Source # 
type AttrLabel SocketSslFallbackPropertyInfo Source # 
type AttrGetType SocketSslFallbackPropertyInfo Source # 
type AttrBaseTypeConstraint SocketSslFallbackPropertyInfo Source # 
type AttrSetTypeConstraint SocketSslFallbackPropertyInfo Source # 
type AttrAllowedOps SocketSslFallbackPropertyInfo Source # 

sslStrict

data SocketSslStrictPropertyInfo Source #

Instances

AttrInfo SocketSslStrictPropertyInfo Source # 
type AttrOrigin SocketSslStrictPropertyInfo Source # 
type AttrLabel SocketSslStrictPropertyInfo Source # 
type AttrGetType SocketSslStrictPropertyInfo Source # 
type AttrBaseTypeConstraint SocketSslStrictPropertyInfo Source # 
type AttrSetTypeConstraint SocketSslStrictPropertyInfo Source # 
type AttrAllowedOps SocketSslStrictPropertyInfo Source # 

timeout

data SocketTimeoutPropertyInfo Source #

Instances

AttrInfo SocketTimeoutPropertyInfo Source # 
type AttrOrigin SocketTimeoutPropertyInfo Source # 
type AttrLabel SocketTimeoutPropertyInfo Source # 
type AttrGetType SocketTimeoutPropertyInfo Source # 
type AttrBaseTypeConstraint SocketTimeoutPropertyInfo Source # 
type AttrSetTypeConstraint SocketTimeoutPropertyInfo Source # 
type AttrAllowedOps SocketTimeoutPropertyInfo Source # 

setSocketTimeout :: (MonadIO m, IsSocket o) => o -> Word32 -> m () Source #

tlsCertificate

data SocketTlsCertificatePropertyInfo Source #

Instances

AttrInfo SocketTlsCertificatePropertyInfo Source # 
type AttrOrigin SocketTlsCertificatePropertyInfo Source # 
type AttrLabel SocketTlsCertificatePropertyInfo Source # 
type AttrGetType SocketTlsCertificatePropertyInfo Source # 
type AttrBaseTypeConstraint SocketTlsCertificatePropertyInfo Source # 
type AttrSetTypeConstraint SocketTlsCertificatePropertyInfo Source # 
type AttrAllowedOps SocketTlsCertificatePropertyInfo Source # 

tlsErrors

data SocketTlsErrorsPropertyInfo Source #

Instances

AttrInfo SocketTlsErrorsPropertyInfo Source # 
type AttrOrigin SocketTlsErrorsPropertyInfo Source # 
type AttrLabel SocketTlsErrorsPropertyInfo Source # 
type AttrGetType SocketTlsErrorsPropertyInfo Source # 
type AttrBaseTypeConstraint SocketTlsErrorsPropertyInfo Source # 
type AttrSetTypeConstraint SocketTlsErrorsPropertyInfo Source # 
type AttrAllowedOps SocketTlsErrorsPropertyInfo Source # 

trustedCertificate

data SocketTrustedCertificatePropertyInfo Source #

Instances

AttrInfo SocketTrustedCertificatePropertyInfo Source # 
type AttrOrigin SocketTrustedCertificatePropertyInfo Source # 
type AttrLabel SocketTrustedCertificatePropertyInfo Source # 
type AttrLabel SocketTrustedCertificatePropertyInfo = "trusted-certificate"
type AttrGetType SocketTrustedCertificatePropertyInfo Source # 
type AttrBaseTypeConstraint SocketTrustedCertificatePropertyInfo Source # 
type AttrSetTypeConstraint SocketTrustedCertificatePropertyInfo Source # 
type AttrAllowedOps SocketTrustedCertificatePropertyInfo Source # 

useThreadContext

data SocketUseThreadContextPropertyInfo Source #

Instances

AttrInfo SocketUseThreadContextPropertyInfo Source # 
type AttrOrigin SocketUseThreadContextPropertyInfo Source # 
type AttrLabel SocketUseThreadContextPropertyInfo Source # 
type AttrLabel SocketUseThreadContextPropertyInfo = "use-thread-context"
type AttrGetType SocketUseThreadContextPropertyInfo Source # 
type AttrBaseTypeConstraint SocketUseThreadContextPropertyInfo Source # 
type AttrSetTypeConstraint SocketUseThreadContextPropertyInfo Source # 
type AttrAllowedOps SocketUseThreadContextPropertyInfo Source # 

Signals

disconnected

event

type C_SocketEventCallback = Ptr () -> CUInt -> Ptr IOStream -> Ptr () -> IO () Source #

newConnection

readable

type C_SocketReadableCallback = Ptr () -> Ptr () -> IO () Source #

writable

type C_SocketWritableCallback = Ptr () -> Ptr () -> IO () Source #