|
Network.Socket | Portability | portable | Stability | provisional | Maintainer | libraries@haskell.org |
|
|
|
|
|
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) | | | | | | | | | | type HostAddress = Word32 | | | | type ProtocolNumber = CInt | | newtype PortNumber = PortNum Word16 | | socket :: Family -> SocketType -> ProtocolNumber -> IO Socket | | socketPair :: Family -> SocketType -> ProtocolNumber -> IO (Socket, 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 | | getPeerCred :: Socket -> IO (CUInt, CUInt, CUInt) | | 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 | | | | getSocketOption :: Socket -> SocketOption -> IO Int | | setSocketOption :: Socket -> SocketOption -> Int -> IO () | | sendFd :: Socket -> CInt -> IO () | | recvFd :: Socket -> IO CInt | | sendAncillary :: Socket -> Int -> Int -> Int -> Ptr a -> Int -> IO () | | recvAncillary :: Socket -> Int -> Int -> IO (Int, Int, Ptr a, Int) | | aNY_PORT :: PortNumber | | iNADDR_ANY :: HostAddress | | sOMAXCONN :: Int | | sOL_SOCKET :: Int | | sCM_RIGHTS :: 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 |
Constructors | | Instances | |
|
|
data Family |
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_SNA | | AF_DECnet | | AF_APPLETALK | | AF_ROUTE | | AF_X25 | | AF_AX25 | | AF_IPX | | AF_NETROM | | AF_BRIDGE | | AF_ATMPVC | | AF_ROSE | | AF_NETBEUI | | AF_SECURITY | | AF_PACKET | | AF_ASH | | AF_ECONET | | AF_ATMSVC | | AF_IRDA | | AF_PPPOX | | AF_WANPIPE | | AF_BLUETOOTH | |
| Instances | |
|
|
data SocketType |
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 | |
| Instances | |
|
|
data SockAddr |
Constructors | | Instances | |
|
|
data SocketStatus |
Constructors | NotConnected | | Bound | | Listening | | Connected | | ConvertedToHandle | |
| Instances | |
|
|
type HostAddress = Word32 |
|
data ShutdownCmd |
Constructors | ShutdownReceive | | ShutdownSend | | ShutdownBoth | |
| Instances | |
|
|
type ProtocolNumber = CInt |
|
newtype PortNumber |
Constructors | | Instances | |
|
|
Socket Operations
|
|
socket :: Family -> SocketType -> ProtocolNumber -> IO Socket |
|
socketPair :: Family -> SocketType -> ProtocolNumber -> IO (Socket, 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 |
|
getPeerCred :: Socket -> IO (CUInt, CUInt, CUInt) |
Returns the processID, userID and groupID of the socket's peer.
Only available on platforms that support SO_PEERCRED on domain sockets.
|
|
socketPort :: Socket -> IO PortNumber |
|
socketToHandle :: Socket -> IOMode -> IO Handle |
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 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 () |
Closes a socket
|
|
Predicates on sockets
|
|
sIsConnected :: Socket -> IO Bool |
|
sIsBound :: Socket -> IO Bool |
|
sIsListening :: Socket -> IO Bool |
|
sIsReadable :: Socket -> IO Bool |
|
sIsWritable :: Socket -> IO Bool |
|
Socket options
|
|
data SocketOption |
Constructors | DummySocketOption__ | | Debug | | ReuseAddr | | Type | | SoError | | DontRoute | | Broadcast | | SendBuffer | | RecvBuffer | | KeepAlive | | OOBInline | | TimeToLive | | MaxSegment | | NoDelay | | Linger | | RecvLowWater | | SendLowWater | | RecvTimeOut | | SendTimeOut | |
| Instances | |
|
|
getSocketOption :: Socket -> SocketOption -> IO Int |
|
setSocketOption :: Socket -> SocketOption -> Int -> IO () |
|
File descriptor transmission
|
|
sendFd :: Socket -> CInt -> IO () |
|
recvFd :: Socket -> IO CInt |
|
sendAncillary :: Socket -> Int -> Int -> Int -> Ptr a -> Int -> IO () |
|
recvAncillary :: Socket -> Int -> Int -> IO (Int, Int, Ptr a, Int) |
|
Special Constants
|
|
aNY_PORT :: PortNumber |
|
iNADDR_ANY :: HostAddress |
|
sOMAXCONN :: Int |
|
sOL_SOCKET :: Int |
|
sCM_RIGHTS :: Int |
|
maxListenQueue :: Int |
|
Initialisation
|
|
withSocketsDo :: IO a -> IO a |
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 -> CInt |
|
mkSocket :: CInt -> Family -> SocketType -> ProtocolNumber -> SocketStatus -> IO Socket |
|
Internal
|
|
The following are exported ONLY for use in the BSD module and
should not be used anywhere else.
|
|
packFamily :: Family -> CInt |
|
unpackFamily :: CInt -> Family |
|
packSocketType :: SocketType -> CInt |
|
throwSocketErrorIfMinus1_ :: Num a => String -> IO a -> IO () |
|
Produced by Haddock version 0.8 |