network-2.1.0.0: Networking-related facilitiesSource codeContentsIndex
Network.Socket
Portabilityportable
Stabilityprovisional
Maintainerlibraries@haskell.org
Contents
Types
Address operations
Socket Operations
Predicates on sockets
Socket options
File descriptor transmission
Special Constants
Initialisation
Very low level operations
Internal
Description

The Network.Socket module is for when you want full control over sockets. Essentially the entire C socket API is exposed through this module; in general the operations follow the behaviour of the C functions of the same name (consult your favourite Unix networking book).

A higher level interface to networking operations is provided through the module Network.

Synopsis
data Socket = MkSocket CInt Family SocketType ProtocolNumber (MVar SocketStatus)
data Family
= AF_UNSPEC
| AF_UNIX
| AF_INET
| AF_INET6
| AF_IMPLINK
| AF_PUP
| AF_CHAOS
| AF_NS
| AF_ECMA
| AF_DATAKIT
| AF_CCITT
| AF_SNA
| AF_DECnet
| AF_DLI
| AF_LAT
| AF_HYLINK
| AF_APPLETALK
| AF_NETBIOS
| AF_ISO
| AF_OSI
| AF_IPX
data SocketType
= NoSocketType
| Stream
| Datagram
| Raw
| RDM
| SeqPacket
data SockAddr = SockAddrInet PortNumber HostAddress
data SocketStatus
= NotConnected
| Bound
| Listening
| Connected
| ConvertedToHandle
type HostAddress = Word32
data ShutdownCmd
= ShutdownReceive
| ShutdownSend
| ShutdownBoth
type ProtocolNumber = CInt
defaultProtocol :: ProtocolNumber
newtype PortNumber = PortNum Word16
type HostName = String
type ServiceName = String
socket :: Family -> SocketType -> ProtocolNumber -> IO Socket
connect :: Socket -> SockAddr -> IO ()
bindSocket :: Socket -> SockAddr -> IO ()
listen :: Socket -> Int -> IO ()
accept :: Socket -> IO (Socket, SockAddr)
getPeerName :: Socket -> IO SockAddr
getSocketName :: Socket -> IO SockAddr
socketPort :: Socket -> IO PortNumber
socketToHandle :: Socket -> IOMode -> IO Handle
sendTo :: Socket -> String -> SockAddr -> IO Int
sendBufTo :: Socket -> Ptr a -> Int -> SockAddr -> IO Int
recvFrom :: Socket -> Int -> IO (String, Int, SockAddr)
recvBufFrom :: Socket -> Ptr a -> Int -> IO (Int, SockAddr)
send :: Socket -> String -> IO Int
recv :: Socket -> Int -> IO String
recvLen :: Socket -> Int -> IO (String, Int)
inet_addr :: String -> IO HostAddress
inet_ntoa :: HostAddress -> IO String
shutdown :: Socket -> ShutdownCmd -> IO ()
sClose :: Socket -> IO ()
sIsConnected :: Socket -> IO Bool
sIsBound :: Socket -> IO Bool
sIsListening :: Socket -> IO Bool
sIsReadable :: Socket -> IO Bool
sIsWritable :: Socket -> IO Bool
data SocketOption
= DummySocketOption__
| Debug
| ReuseAddr
| Type
| SoError
| DontRoute
| Broadcast
| SendBuffer
| RecvBuffer
| KeepAlive
| OOBInline
| NoDelay
| Linger
| RecvLowWater
| SendLowWater
| RecvTimeOut
| SendTimeOut
| UseLoopBack
getSocketOption :: Socket -> SocketOption -> IO Int
setSocketOption :: Socket -> SocketOption -> Int -> IO ()
aNY_PORT :: PortNumber
iNADDR_ANY :: HostAddress
sOMAXCONN :: Int
sOL_SOCKET :: Int
maxListenQueue :: Int
withSocketsDo :: IO a -> IO a
fdSocket :: Socket -> CInt
mkSocket :: CInt -> Family -> SocketType -> ProtocolNumber -> SocketStatus -> IO Socket
packFamily :: Family -> CInt
unpackFamily :: CInt -> Family
packSocketType :: SocketType -> CInt
throwSocketErrorIfMinus1_ :: Num a => String -> IO a -> IO ()
Types
data Socket Source
Constructors
MkSocket CInt Family SocketType ProtocolNumber (MVar SocketStatus)
show/hide Instances
data Family Source

Address Families.

This data type might have different constructors depending on what is supported by the operating system.

Constructors
AF_UNSPEC
AF_UNIX
AF_INET
AF_INET6
AF_IMPLINK
AF_PUP
AF_CHAOS
AF_NS
AF_ECMA
AF_DATAKIT
AF_CCITT
AF_SNA
AF_DECnet
AF_DLI
AF_LAT
AF_HYLINK
AF_APPLETALK
AF_NETBIOS
AF_ISO
AF_OSI
AF_IPX
show/hide Instances
data SocketType Source

Socket Types.

This data type might have different constructors depending on what is supported by the operating system.

Constructors
NoSocketType
Stream
Datagram
Raw
RDM
SeqPacket
show/hide Instances
data SockAddr Source
Constructors
SockAddrInet PortNumber HostAddress
show/hide Instances
data SocketStatus Source
Constructors
NotConnected
Bound
Listening
Connected
ConvertedToHandle
show/hide Instances
type HostAddress = Word32Source
data ShutdownCmd Source
Constructors
ShutdownReceive
ShutdownSend
ShutdownBoth
show/hide Instances
type ProtocolNumber = CIntSource
defaultProtocol :: ProtocolNumberSource
This is the default protocol for a given service.
newtype PortNumber Source
Constructors
PortNum Word16
show/hide Instances
Address operations
type HostName = StringSource
type ServiceName = StringSource
Socket Operations
socket :: Family -> SocketType -> ProtocolNumber -> IO SocketSource
connect :: Socket -> SockAddr -> IO ()Source
bindSocket :: Socket -> SockAddr -> IO ()Source
listen :: Socket -> Int -> IO ()Source
accept :: Socket -> IO (Socket, SockAddr)Source
getPeerName :: Socket -> IO SockAddrSource
getSocketName :: Socket -> IO SockAddrSource
socketPort :: Socket -> IO PortNumberSource
socketToHandle :: Socket -> IOMode -> IO HandleSource

turns a Socket into an Handle. By default, the new handle is unbuffered. Use hSetBuffering to change the buffering.

Note that since a Handle is automatically closed by a finalizer when it is no longer referenced, you should avoid doing any more operations on the Socket after calling socketToHandle. To close the Socket after socketToHandle, call hClose on the Handle.

sendTo :: Socket -> String -> SockAddr -> IO IntSource
sendBufTo :: Socket -> Ptr a -> Int -> SockAddr -> IO IntSource
recvFrom :: Socket -> Int -> IO (String, Int, SockAddr)Source
recvBufFrom :: Socket -> Ptr a -> Int -> IO (Int, SockAddr)Source
send :: Socket -> String -> IO IntSource
recv :: Socket -> Int -> IO StringSource
recvLen :: Socket -> Int -> IO (String, Int)Source
inet_addr :: String -> IO HostAddressSource
inet_ntoa :: HostAddress -> IO StringSource
shutdown :: Socket -> ShutdownCmd -> IO ()Source
sClose :: Socket -> IO ()Source
Closes a socket
Predicates on sockets
sIsConnected :: Socket -> IO BoolSource
sIsBound :: Socket -> IO BoolSource
sIsListening :: Socket -> IO BoolSource
sIsReadable :: Socket -> IO BoolSource
sIsWritable :: Socket -> IO BoolSource
Socket options
data SocketOption Source
Constructors
DummySocketOption__
Debug
ReuseAddr
Type
SoError
DontRoute
Broadcast
SendBuffer
RecvBuffer
KeepAlive
OOBInline
NoDelay
Linger
RecvLowWater
SendLowWater
RecvTimeOut
SendTimeOut
UseLoopBack
show/hide Instances
getSocketOption :: Socket -> SocketOption -> IO IntSource
setSocketOption :: Socket -> SocketOption -> Int -> IO ()Source
File descriptor transmission
Special Constants
aNY_PORT :: PortNumberSource
iNADDR_ANY :: HostAddressSource
The IPv4 wild card address.
sOMAXCONN :: IntSource
sOL_SOCKET :: IntSource
maxListenQueue :: IntSource
Initialisation
withSocketsDo :: IO a -> IO aSource

On Windows operating systems, the networking subsystem has to be initialised using withSocketsDo before any networking operations can be used. eg.

 main = withSocketsDo $ do {...}

Although this is only strictly necessary on Windows platforms, it is harmless on other platforms, so for portability it is good practice to use it all the time.

Very low level operations
fdSocket :: Socket -> CIntSource
mkSocket :: CInt -> Family -> SocketType -> ProtocolNumber -> SocketStatus -> IO SocketSource
Internal
The following are exported ONLY for use in the BSD module and should not be used anywhere else.
packFamily :: Family -> CIntSource
unpackFamily :: CInt -> FamilySource
packSocketType :: SocketType -> CIntSource
throwSocketErrorIfMinus1_ :: Num a => String -> IO a -> IO ()Source
Produced by Haddock version 0.8