socket-sctp-0.1.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 :: MessageFlags )
    ( 2      :: StreamNumber )
    ( 0      :: TimeToLive )
    ( 0      :: Context )

data SCTP Source

Instances

Operations

receiveMessage

receiveMessage Source

Arguments

:: Family f 
=> Socket f SequentialPacket SCTP 
-> Int

buffer size in bytes

-> MessageFlags 
-> IO (ByteString, SocketAddress f, SendReceiveInfo, MessageFlags) 

Receive a message on a SCTP socket.

  • Everything that applies to recv 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

:: Family f 
=> Socket f SequentialPacket SCTP 
-> ByteString 
-> SocketAddress f 
-> PayloadProtocolIdentifier

a user value not interpreted by SCTP

-> MessageFlags 
-> 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

SendReceiveInfoFlags

unordered

addressOverride

abort

shutdown

Socket Options

InitMessage

data InitMessage Source

SCTP_INITMSG

Constructors

InitMessage 

Fields

outboundStreams :: Word16

number of outbound streams

maxInboundStreams :: Word16

max number of inbound streams

maxAttempts :: Word16

max number re-transmissions while establishing an association

maxInitTimeout :: Word16

time-out in milliseconds for establishing an association

Events