Copyright | (c) Lars Petersen 2015 |
---|---|
License | MIT |
Maintainer | info@lars-petersen.net |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
System.Socket.Protocol.SCTP
Contents
Description
- data SCTP
- receiveMessage :: (Family f, Storable (SocketAddress f), SCTPType t) => Socket f t SCTP -> Int -> MessageFlags -> IO (ByteString, SocketAddress f, SendReceiveInfo, MessageFlags)
- sendMessage :: Storable (SocketAddress f) => Socket f t SCTP -> ByteString -> Maybe (SocketAddress f) -> PayloadProtocolIdentifier -> SendmsgFlags -> StreamNumber -> TimeToLive -> Context -> IO Int
- data SendReceiveInfo = SendReceiveInfo {
- sinfoStreamNumber :: StreamNumber
- sinfoStreamSequenceNumber :: StreamSequenceNumber
- sinfoFlags :: SendReceiveInfoFlags
- sinfoPayloadProtocolIdentifier :: PayloadProtocolIdentifier
- sinfoContext :: Context
- sinfoTimeToLive :: TimeToLive
- sinfoTransportSequenceNumber :: TransportSequenceNumber
- sinfoCumulativeTransportSequenceNumber :: CumulativeTransportSequenceNumber
- sinfoAssociationIdentifier :: AssociationIdentifier
- newtype StreamNumber = StreamNumber Word16
- newtype StreamSequenceNumber = StreamSequenceNumber Word16
- newtype PayloadProtocolIdentifier = PayloadProtocolIdentifier Word32
- newtype Context = Context Word32
- newtype TimeToLive = TimeToLive Word32
- newtype TransportSequenceNumber = TransportSequenceNumber Word32
- newtype CumulativeTransportSequenceNumber = CumulativeTransportSequenceNumber Word32
- newtype AssociationIdentifier = AssociationIdentifier Word32
- newtype SendmsgFlags = SendmsgFlags Word32
- unorderedSendmsg :: SendmsgFlags
- newtype SendReceiveInfoFlags = SendReceiveInfoFlags Word16
- unordered :: SendReceiveInfoFlags
- addressOverride :: SendReceiveInfoFlags
- abort :: SendReceiveInfoFlags
- shutdown :: SendReceiveInfoFlags
- data InitMessage = InitMessage {}
- data Events = Events {}
- msgNotification :: MessageFlags
- data Notification
- data AssocId
- unsafeParseNotification :: ByteString -> IO Notification
- data AssocChange = AssocChange {
- acState :: !AcState
- acError :: !Word16
- acOutboundStreams :: !Word16
- acInboundStreams :: !Word16
- acAssocId :: !AssocId
- acInfo :: !ByteString
- data AcState
Examples
Server
{-# LANGUAGE OverloadedStrings #-} module Main where import Data.Monoid import Control.Monad import System.Socket import System.Socket.Family.Inet as Inet import System.Socket.Protocol.SCTP as SCTP main :: IO () main = do server <- socket :: IO (Socket Inet SequentialPacket SCTP) bind server (SocketAddressInet Inet.loopback 7777) listen server 5 setSocketOption server (mempty { dataIOEvent = True }) forever $ do x@(msg, adr, sinfo, flags) <- SCTP.receiveMessage server 4096 mempty print x
Client
{-# LANGUAGE OverloadedStrings #-} module Main where import Data.Monoid import Control.Monad import System.Socket import System.Socket.Family.Inet as Inet import System.Socket.Protocol.SCTP as SCTP main :: IO () main = do client <- socket :: IO (Socket Inet SequentialPacket SCTP) print =<< SCTP.sendMessage client "Hello world!" ( SocketAddressInet Inet.loopback 7777 ) ( 2342 :: PayloadProtocolIdentifier ) ( mempty :: SendmsgFlags ) ( 2 :: StreamNumber ) ( 0 :: TimeToLive ) ( 0 :: Context )
Operations
receiveMessage
Arguments
:: (Family f, Storable (SocketAddress f), SCTPType t) | |
=> Socket f t SCTP | |
-> Int | buffer size in bytes |
-> MessageFlags | |
-> IO (ByteString, SocketAddress f, SendReceiveInfo, MessageFlags) |
Receive a message on a SCTP socket.
- Everything that applies to
receive
is also true for this operation. - The fields of the
SendReceiveInfo
structure are only filled ifdataIOEvent
has been enabled trough theEvents
socket option. - If the supplied buffer size is not sufficient, several consecutive reads are
necessary to receive the complete message. The
msgEndOfRecord
flag is set when the message has been read completely.
sendMessage
Arguments
:: Storable (SocketAddress f) | |
=> Socket f t SCTP | |
-> ByteString | |
-> Maybe (SocketAddress f) | |
-> PayloadProtocolIdentifier | a user value not interpreted by SCTP |
-> SendmsgFlags | |
-> StreamNumber | |
-> TimeToLive | |
-> Context | |
-> IO Int |
Send a message on a SCTP socket.
- Everything that applies to
send
is also true for this operation. - Sending a message is atomic unless the
ExplicitEndOfRecord
option has been enabled (not yet supported),
SendReceiveInfo
data SendReceiveInfo Source #
Constructors
Instances
newtype StreamSequenceNumber Source #
Constructors
StreamSequenceNumber Word16 |
newtype PayloadProtocolIdentifier Source #
Constructors
PayloadProtocolIdentifier Word32 |
newtype TransportSequenceNumber Source #
Constructors
TransportSequenceNumber Word32 |
newtype CumulativeTransportSequenceNumber Source #
Constructors
CumulativeTransportSequenceNumber Word32 |
newtype AssociationIdentifier Source #
Constructors
AssociationIdentifier Word32 |
SendmsgFlags
newtype SendmsgFlags Source #
Constructors
SendmsgFlags Word32 |
SendReceiveInfoFlags
newtype SendReceiveInfoFlags Source #
Constructors
SendReceiveInfoFlags Word16 |
unordered
addressOverride
abort
shutdown
Socket Options
InitMessage
data InitMessage Source #
SCTP_INITMSG
Constructors
InitMessage | |
Fields
|
Events
SCTP_EVENTS
Constructors
Events | |
Fields |
Notifications
data Notification Source #
Constructors
AssocChangeNotification !AssocChange | |
UnsupportedNotification !ByteString |
Instances
unsafeParseNotification :: ByteString -> IO Notification Source #
Parse an SCTP notification.
This assumes that the buffer contains a complete notification (i.e. MSG_EOR was set on the last chunk it contains), and is thus unsafe. Unfortunately, because of the possibility of partial notifications from a too-small buffer for recvmsg, this must be exposed to users.
SCTP_ASSOC_CHANGE
data AssocChange Source #
Constructors
AssocChange | |
Fields
|
Instances
Constructors
COMM_UP | |
COMM_LOST | |
RESTART | |
SHUTDOWN_COMP | |
CANT_STR_ASSOC | |
UNKNOWN_AC_STATE |