socket-sctp-0.2.0.0: STCP socket extensions library.

Copyright(c) Lars Petersen 2015
LicenseMIT
Maintainerinfo@lars-petersen.net
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

System.Socket.Protocol.SCTP

Contents

Description

 

Synopsis

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 )

data SCTP Source #

Instances

Operations

receiveMessage

receiveMessage Source #

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 if dataIOEvent has been enabled trough the Events 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

sendMessage Source #

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

newtype StreamSequenceNumber Source #

Instances

Eq StreamSequenceNumber Source # 
Num StreamSequenceNumber Source # 
Ord StreamSequenceNumber Source # 
Show StreamSequenceNumber Source # 
Storable StreamSequenceNumber Source # 

newtype PayloadProtocolIdentifier Source #

Instances

Eq PayloadProtocolIdentifier Source # 
Num PayloadProtocolIdentifier Source # 
Ord PayloadProtocolIdentifier Source # 
Show PayloadProtocolIdentifier Source # 
Storable PayloadProtocolIdentifier Source # 

newtype TransportSequenceNumber Source #

Instances

Eq TransportSequenceNumber Source # 
Num TransportSequenceNumber Source # 
Ord TransportSequenceNumber Source # 
Show TransportSequenceNumber Source # 
Storable TransportSequenceNumber Source # 

newtype CumulativeTransportSequenceNumber Source #

Instances

Eq CumulativeTransportSequenceNumber Source # 
Num CumulativeTransportSequenceNumber Source # 
Ord CumulativeTransportSequenceNumber Source # 
Show CumulativeTransportSequenceNumber Source # 
Storable CumulativeTransportSequenceNumber Source # 

newtype AssociationIdentifier Source #

Instances

Eq AssociationIdentifier Source # 
Num AssociationIdentifier Source # 
Ord AssociationIdentifier Source # 
Show AssociationIdentifier Source # 
Storable AssociationIdentifier Source # 

SendmsgFlags

newtype SendmsgFlags Source #

Constructors

SendmsgFlags Word32 

Instances

Eq SendmsgFlags Source # 
Num SendmsgFlags Source # 
Ord SendmsgFlags Source # 
Show SendmsgFlags Source # 
Monoid SendmsgFlags Source # 
Storable SendmsgFlags Source # 
Bits SendmsgFlags Source # 

SendReceiveInfoFlags

newtype SendReceiveInfoFlags Source #

Instances

Eq SendReceiveInfoFlags Source # 
Num SendReceiveInfoFlags Source # 
Ord SendReceiveInfoFlags Source # 
Show SendReceiveInfoFlags Source # 
Storable SendReceiveInfoFlags Source # 
Bits SendReceiveInfoFlags Source # 

unordered

addressOverride

abort

shutdown

Socket Options

InitMessage

data InitMessage Source #

SCTP_INITMSG

Constructors

InitMessage 

Fields

Events

Notifications

data AssocId Source #

Instances

Bounded AssocId Source # 
Enum AssocId Source # 
Eq AssocId Source # 

Methods

(==) :: AssocId -> AssocId -> Bool #

(/=) :: AssocId -> AssocId -> Bool #

Integral AssocId Source # 
Num AssocId Source # 
Ord AssocId Source # 
Read AssocId Source # 
Real AssocId Source # 
Show AssocId Source # 
Ix AssocId Source # 
Storable AssocId Source # 
Bits AssocId Source # 

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