| Copyright | (c) The University of Glasgow 2001 | 
|---|---|
| License | BSD-style (see the file libraries/network/LICENSE) | 
| Maintainer | libraries@haskell.org | 
| Stability | provisional | 
| Portability | portable | 
| Safe Haskell | None | 
| Language | Haskell98 | 
Network.Socket
Contents
Description
This is the main module of the network package supposed to be used with either Network.Socket.ByteString or Network.Socket.ByteString.Lazy for sending/receiving.
Here are two minimal example programs using the TCP/IP protocol: a server that echoes all data that it receives back (servicing only one client) and a client using it.
-- Echo server program
module Main (main) where
import Control.Concurrent (forkFinally)
import qualified Control.Exception as E
import Control.Monad (unless, forever, void)
import qualified Data.ByteString as S
import Network.Socket hiding (recv)
import Network.Socket.ByteString (recv, sendAll)
main :: IO ()
main = withSocketsDo $ do
    addr <- resolve "3000"
    E.bracket (open addr) close loop
  where
    resolve port = do
        let hints = defaultHints {
                addrFlags = [AI_PASSIVE]
              , addrSocketType = Stream
              }
        addr:_ <- getAddrInfo (Just hints) Nothing (Just port)
        return addr
    open addr = do
        sock <- socket (addrFamily addr) (addrSocketType addr) (addrProtocol addr)
        setSocketOption sock ReuseAddr 1
        bind sock (addrAddress addr)
        -- If the prefork technique is not used,
        -- set CloseOnExec for the security reasons.
        let fd = fdSocket sock
        setCloseOnExecIfNeeded fd
        listen sock 10
        return sock
    loop sock = forever $ do
        (conn, peer) <- accept sock
        putStrLn $ "Connection from " ++ show peer
        void $ forkFinally (talk conn) (\_ -> close conn)
    talk conn = do
        msg <- recv conn 1024
        unless (S.null msg) $ do
          sendAll conn msg
          talk conn{-# LANGUAGE OverloadedStrings #-}
-- Echo client program
module Main (main) where
import qualified Control.Exception as E
import qualified Data.ByteString.Char8 as C
import Network.Socket hiding (recv)
import Network.Socket.ByteString (recv, sendAll)
main :: IO ()
main = withSocketsDo $ do
    addr <- resolve "127.0.0.1" "3000"
    E.bracket (open addr) close talk
  where
    resolve host port = do
        let hints = defaultHints { addrSocketType = Stream }
        addr:_ <- getAddrInfo (Just hints) (Just host) (Just port)
        return addr
    open addr = do
        sock <- socket (addrFamily addr) (addrSocketType addr) (addrProtocol addr)
        connect sock $ addrAddress addr
        return sock
    talk sock = do
        sendAll sock "Hello, world!"
        msg <- recv sock 1024
        putStr "Received: "
        C.putStrLn msgThe proper programming model is that one Socket is handled by
 a single thread. If multiple threads use one Socket concurrently,
 unexpected things would happen. There is one exception for multiple
 threads vs a single Socket: one thread reads data from a Socket
 only and the other thread writes data to the Socket only.
Synopsis
- withSocketsDo :: IO a -> IO a
- getAddrInfo :: Maybe AddrInfo -> Maybe HostName -> Maybe ServiceName -> IO [AddrInfo]
- type HostName = String
- type ServiceName = String
- data AddrInfo = AddrInfo {}
- defaultHints :: AddrInfo
- data AddrInfoFlag
- addrInfoFlagImplemented :: AddrInfoFlag -> Bool
- connect :: Socket -> SockAddr -> IO ()
- bind :: Socket -> SockAddr -> IO ()
- listen :: Socket -> Int -> IO ()
- accept :: Socket -> IO (Socket, SockAddr)
- close :: Socket -> IO ()
- close' :: Socket -> IO ()
- shutdown :: Socket -> ShutdownCmd -> IO ()
- data ShutdownCmd
- data SocketOption
- isSupportedSocketOption :: SocketOption -> Bool
- getSocketOption :: Socket -> SocketOption -> IO Int
- setSocketOption :: Socket -> SocketOption -> Int -> IO ()
- data Socket = MkSocket CInt Family SocketType ProtocolNumber (MVar SocketStatus)
- socket :: Family -> SocketType -> ProtocolNumber -> IO Socket
- fdSocket :: Socket -> CInt
- mkSocket :: CInt -> Family -> SocketType -> ProtocolNumber -> SocketStatus -> IO Socket
- socketToHandle :: Socket -> IOMode -> IO Handle
- data SocketType
- isSupportedSocketType :: SocketType -> Bool
- data Family- = AF_UNSPEC
- | AF_UNIX
- | AF_INET
- | AF_INET6
- | AF_IMPLINK
- | AF_PUP
- | AF_CHAOS
- | AF_NS
- | AF_NBS
- | AF_ECMA
- | AF_DATAKIT
- | AF_CCITT
- | AF_SNA
- | AF_DECnet
- | AF_DLI
- | AF_LAT
- | AF_HYLINK
- | AF_APPLETALK
- | AF_ROUTE
- | AF_NETBIOS
- | AF_NIT
- | AF_802
- | AF_ISO
- | AF_OSI
- | AF_NETMAN
- | AF_X25
- | AF_AX25
- | AF_OSINET
- | AF_GOSSIP
- | AF_IPX
- | Pseudo_AF_XTP
- | AF_CTF
- | AF_WAN
- | AF_SDL
- | AF_NETWARE
- | AF_NDD
- | AF_INTF
- | AF_COIP
- | AF_CNT
- | Pseudo_AF_RTIP
- | Pseudo_AF_PIP
- | AF_SIP
- | AF_ISDN
- | Pseudo_AF_KEY
- | AF_NATM
- | AF_ARP
- | Pseudo_AF_HDRCMPLT
- | AF_ENCAP
- | AF_LINK
- | AF_RAW
- | AF_RIF
- | 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
- | AF_CAN
 
- isSupportedFamily :: Family -> Bool
- type ProtocolNumber = CInt
- defaultProtocol :: ProtocolNumber
- data SockAddr
- isSupportedSockAddr :: SockAddr -> Bool
- getPeerName :: Socket -> IO SockAddr
- getSocketName :: Socket -> IO SockAddr
- type HostAddress = Word32
- hostAddressToTuple :: HostAddress -> (Word8, Word8, Word8, Word8)
- tupleToHostAddress :: (Word8, Word8, Word8, Word8) -> HostAddress
- type HostAddress6 = (Word32, Word32, Word32, Word32)
- hostAddress6ToTuple :: HostAddress6 -> (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16)
- tupleToHostAddress6 :: (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> HostAddress6
- type FlowInfo = Word32
- type ScopeID = Word32
- ifNameToIndex :: String -> IO (Maybe Int)
- ifIndexToName :: Int -> IO (Maybe String)
- newtype PortNumber = PortNum Word16
- defaultPort :: PortNumber
- socketPortSafe :: Socket -> IO (Maybe PortNumber)
- socketPort :: Socket -> IO PortNumber
- isUnixDomainSocketAvailable :: Bool
- socketPair :: Family -> SocketType -> ProtocolNumber -> IO (Socket, Socket)
- sendFd :: Socket -> CInt -> IO ()
- recvFd :: Socket -> IO CInt
- getPeerCredential :: Socket -> IO (Maybe CUInt, Maybe CUInt, Maybe CUInt)
- data NameInfoFlag
- getNameInfo :: [NameInfoFlag] -> Bool -> Bool -> SockAddr -> IO (Maybe HostName, Maybe ServiceName)
- setCloseOnExecIfNeeded :: CInt -> IO ()
- getCloseOnExec :: CInt -> IO Bool
- setNonBlockIfNeeded :: CInt -> IO ()
- getNonBlock :: CInt -> IO Bool
- sendBuf :: Socket -> Ptr Word8 -> Int -> IO Int
- recvBuf :: Socket -> Ptr Word8 -> Int -> IO Int
- sendBufTo :: Socket -> Ptr a -> Int -> SockAddr -> IO Int
- recvBufFrom :: Socket -> Ptr a -> Int -> IO (Int, SockAddr)
- maxListenQueue :: Int
- send :: Socket -> String -> IO Int
- sendTo :: Socket -> String -> SockAddr -> IO Int
- recv :: Socket -> Int -> IO String
- recvFrom :: Socket -> Int -> IO (String, Int, SockAddr)
- recvLen :: Socket -> Int -> IO (String, Int)
- htonl :: Word32 -> Word32
- ntohl :: Word32 -> Word32
- inet_addr :: String -> IO HostAddress
- inet_ntoa :: HostAddress -> IO String
- bindSocket :: Socket -> SockAddr -> IO ()
- sClose :: Socket -> IO ()
- data SocketStatus
- isConnected :: Socket -> IO Bool
- isBound :: Socket -> IO Bool
- isListening :: Socket -> IO Bool
- isReadable :: Socket -> IO Bool
- isWritable :: Socket -> IO Bool
- sIsConnected :: Socket -> IO Bool
- sIsBound :: Socket -> IO Bool
- sIsListening :: Socket -> IO Bool
- sIsReadable :: Socket -> IO Bool
- sIsWritable :: Socket -> IO Bool
- aNY_PORT :: PortNumber
- iNADDR_ANY :: HostAddress
- iN6ADDR_ANY :: HostAddress6
- sOMAXCONN :: Int
- sOL_SOCKET :: Int
- sCM_RIGHTS :: Int
- packFamily :: Family -> CInt
- unpackFamily :: CInt -> Family
- packSocketType :: SocketType -> CInt
- getPeerCred :: Socket -> IO (CUInt, CUInt, CUInt)
Initialisation
withSocketsDo :: IO a -> IO a Source #
With older versions of the network library (version 2.6.0.2 or earlier)
on Windows operating systems,
the networking subsystem must be initialised using withSocketsDo before
any networking operations can be used. eg.
main = withSocketsDo $ do {...}It is fine to nest calls to withSocketsDo, and to perform networking operations
after withSocketsDo has returned.
In newer versions of the network library (version v2.6.1.0 or later)
it is only necessary to call
withSocketsDo if you are calling the MkSocket constructor directly.
However, for compatibility with older versions on Windows, it is good practice
to always call withSocketsDo (it's very cheap).
Address information
Arguments
| :: Maybe AddrInfo | preferred socket type or protocol | 
| -> Maybe HostName | host name to look up | 
| -> Maybe ServiceName | service name to look up | 
| -> IO [AddrInfo] | resolved addresses, with "best" first | 
Resolve a host or service name to one or more addresses.
 The AddrInfo values that this function returns contain SockAddr
 values that you can pass directly to connect or
 bind.
This function is protocol independent. It can return both IPv4 and IPv6 address information.
The AddrInfo argument specifies the preferred query behaviour,
 socket options, or protocol.  You can override these conveniently
 using Haskell's record update syntax on defaultHints, for example
 as follows:
>>>let hints = defaultHints { addrFlags = [AI_NUMERICHOST], addrSocketType = Stream }
You must provide a Just value for at least one of the HostName
 or ServiceName arguments.  HostName can be either a numeric
 network address (dotted quad for IPv4, colon-separated hex for
 IPv6) or a hostname.  In the latter case, its addresses will be
 looked up unless AI_NUMERICHOST is specified as a hint.  If you
 do not provide a HostName value and do not set AI_PASSIVE as
 a hint, network addresses in the result will contain the address of
 the loopback interface.
If the query fails, this function throws an IO exception instead of
 returning an empty list.  Otherwise, it returns a non-empty list
 of AddrInfo values.
There are several reasons why a query might result in several values. For example, the queried-for host could be multihomed, or the service might be available via several protocols.
Note: the order of arguments is slightly different to that defined
 for getaddrinfo in RFC 2553.  The AddrInfo parameter comes first
 to make partial application easier.
>>>addr:_ <- getAddrInfo (Just hints) (Just "127.0.0.1") (Just "http")>>>addrAddress addr127.0.0.1:80
Types
type HostName = String Source #
Either a host name e.g., "haskell.org" or a numeric host
 address string consisting of a dotted decimal IPv4 address or an
 IPv6 address e.g., "192.168.0.1".
type ServiceName = String Source #
Constructors
| AddrInfo | |
| Fields | |
Instances
| Eq AddrInfo Source # | |
| Show AddrInfo Source # | |
| Storable AddrInfo Source # | |
| Defined in Network.Socket | |
defaultHints :: AddrInfo Source #
Default hints for address lookup with getAddrInfo.  The values
 of the addrAddress and addrCanonName fields are undefined,
 and are never inspected by getAddrInfo.
>>>addrFlags defaultHints[]>>>addrFamily defaultHintsAF_UNSPEC>>>addrSocketType defaultHintsNoSocketType>>>addrProtocol defaultHints0
Flags
data AddrInfoFlag Source #
Flags that control the querying behaviour of getAddrInfo.
   For more information, see https://tools.ietf.org/html/rfc3493#page-25
Constructors
| AI_ADDRCONFIG | The list of returned  | 
| AI_ALL | If  | 
| AI_CANONNAME | The  | 
| AI_NUMERICHOST | The  | 
| AI_NUMERICSERV | The  | 
| AI_PASSIVE | If no  | 
| AI_V4MAPPED | If an IPv6 lookup is performed, and no IPv6 addresses are found, IPv6-mapped IPv4 addresses will be returned. (Only some platforms support this.) | 
Instances
| Eq AddrInfoFlag Source # | |
| Defined in Network.Socket | |
| Read AddrInfoFlag Source # | |
| Defined in Network.Socket Methods readsPrec :: Int -> ReadS AddrInfoFlag # readList :: ReadS [AddrInfoFlag] # | |
| Show AddrInfoFlag Source # | |
| Defined in Network.Socket Methods showsPrec :: Int -> AddrInfoFlag -> ShowS # show :: AddrInfoFlag -> String # showList :: [AddrInfoFlag] -> ShowS # | |
addrInfoFlagImplemented :: AddrInfoFlag -> Bool Source #
Indicate whether the given AddrInfoFlag will have any effect on
 this system.
Socket operations
bind :: Socket -> SockAddr -> IO () Source #
Bind the socket to an address. The socket must not already be
 bound.  The Family passed to bind must be the
 same as that passed to socket.  If the special port number
 defaultPort is passed then the system assigns the next available
 use port.
listen :: Socket -> Int -> IO () Source #
Listen for connections made to the socket. The second argument specifies the maximum number of queued connections and should be at least 1; the maximum value is system-dependent (usually 5).
accept :: Socket -> IO (Socket, SockAddr) Source #
Accept a connection.  The socket must be bound to an address and
 listening for connections.  The return value is a pair (conn,
 address) where conn is a new socket object usable to send and
 receive data on the connection, and address is the address bound
 to the socket on the other end of the connection.
Closing
close :: Socket -> IO () Source #
Close the socket. This function does not throw exceptions even if the underlying system call returns errors.
Sending data to or receiving data from closed socket may lead to undefined behaviour.
If multiple threads use the same socket and one uses fdSocket and
   the other use close, unexpected behavior may happen.
   For more information, please refer to the documentation of fdSocket.
close' :: Socket -> IO () Source #
Close the socket. This function throws exceptions if the underlying system call returns errors.
Sending data to or receiving data from closed socket may lead to undefined behaviour.
shutdown :: Socket -> ShutdownCmd -> IO () Source #
Shut down one or both halves of the connection, depending on the
 second argument to the function.  If the second argument is
 ShutdownReceive, further receives are disallowed.  If it is
 ShutdownSend, further sends are disallowed.  If it is
 ShutdownBoth, further sends and receives are disallowed.
data ShutdownCmd Source #
Constructors
| ShutdownReceive | |
| ShutdownSend | |
| ShutdownBoth | 
Socket options
data SocketOption Source #
Socket options for use with setSocketOption and getSocketOption.
The existence of a constructor does not imply that the relevant option
 is supported on your system: see isSupportedSocketOption
Constructors
| Debug | SO_DEBUG | 
| ReuseAddr | SO_REUSEADDR | 
| Type | SO_TYPE | 
| SoError | SO_ERROR | 
| DontRoute | SO_DONTROUTE | 
| Broadcast | SO_BROADCAST | 
| SendBuffer | SO_SNDBUF | 
| RecvBuffer | SO_RCVBUF | 
| KeepAlive | SO_KEEPALIVE | 
| OOBInline | SO_OOBINLINE | 
| TimeToLive | IP_TTL | 
| MaxSegment | TCP_MAXSEG | 
| NoDelay | TCP_NODELAY | 
| Cork | TCP_CORK | 
| Linger | SO_LINGER | 
| ReusePort | SO_REUSEPORT | 
| RecvLowWater | SO_RCVLOWAT | 
| SendLowWater | SO_SNDLOWAT | 
| RecvTimeOut | SO_RCVTIMEO | 
| SendTimeOut | SO_SNDTIMEO | 
| UseLoopBack | SO_USELOOPBACK | 
| UserTimeout | TCP_USER_TIMEOUT | 
| IPv6Only | IPV6_V6ONLY | 
| CustomSockOpt (CInt, CInt) | 
Instances
| Show SocketOption Source # | |
| Defined in Network.Socket Methods showsPrec :: Int -> SocketOption -> ShowS # show :: SocketOption -> String # showList :: [SocketOption] -> ShowS # | |
isSupportedSocketOption :: SocketOption -> Bool Source #
Does the SocketOption exist on this system?
getSocketOption :: Socket -> SocketOption -> IO Int Source #
Get a socket option that gives an Int value. There is currently no API to get e.g. the timeval socket options
setSocketOption :: Socket -> SocketOption -> Int -> IO () Source #
Set a socket option that expects an Int value. There is currently no API to set e.g. the timeval socket options
Socket
A socket data type.
  Sockets are not GCed unless they are closed by close.
Constructors
| MkSocket CInt Family SocketType ProtocolNumber (MVar SocketStatus) | Deprecated:  | 
socket :: Family -> SocketType -> ProtocolNumber -> IO Socket Source #
Create a new socket using the given address family, socket type
 and protocol number.  The address family is usually AF_INET,
 AF_INET6, or AF_UNIX.  The socket type is usually Stream or
 Datagram.  The protocol number is usually defaultProtocol.
 If AF_INET6 is used and the socket type is Stream or Datagram,
 the IPv6Only socket option is set to 0 so that both IPv4 and IPv6
 can be handled with one socket.
>>>let hints = defaultHints { addrFlags = [AI_NUMERICHOST, AI_NUMERICSERV], addrSocketType = Stream }>>>addr:_ <- getAddrInfo (Just hints) (Just "127.0.0.1") (Just "5000")>>>sock <- socket (addrFamily addr) (addrSocketType addr) (addrProtocol addr)>>>bind sock (addrAddress addr)>>>getSocketName sock127.0.0.1:5000
fdSocket :: Socket -> CInt Source #
Obtaining the file descriptor from a socket.
If a Socket is shared with multiple threads and
   one uses fdSocket, unexpected issues may happen.
   Consider the following scenario:
1) Thread A acquires a Fd from Socket by fdSocket.
2) Thread B close the Socket.
3) Thread C opens a new Socket. Unfortunately it gets the same Fd
      number which thread A is holding.
In this case, it is safer for Thread A to clone Fd by
   dup. But this would still suffer from
   a rase condition between fdSocket and close.
mkSocket :: CInt -> Family -> SocketType -> ProtocolNumber -> SocketStatus -> IO Socket Source #
Smart constructor for constructing a Socket. It should only be
 called once for every new file descriptor. The caller must make
 sure that the socket is in non-blocking mode. See
 setNonBlockIfNeeded.
socketToHandle :: Socket -> IOMode -> IO Handle Source #
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.
Types of Socket
data SocketType Source #
Socket Types.
The existence of a constructor does not necessarily imply that that
 socket type is supported on your system: see isSupportedSocketType.
Constructors
| NoSocketType | 0, used in getAddrInfo hints, for example | 
| Stream | SOCK_STREAM | 
| Datagram | SOCK_DGRAM | 
| Raw | SOCK_RAW | 
| RDM | SOCK_RDM | 
| SeqPacket | SOCK_SEQPACKET | 
Instances
| Eq SocketType Source # | |
| Defined in Network.Socket.Types | |
| Ord SocketType Source # | |
| Defined in Network.Socket.Types Methods compare :: SocketType -> SocketType -> Ordering # (<) :: SocketType -> SocketType -> Bool # (<=) :: SocketType -> SocketType -> Bool # (>) :: SocketType -> SocketType -> Bool # (>=) :: SocketType -> SocketType -> Bool # max :: SocketType -> SocketType -> SocketType # min :: SocketType -> SocketType -> SocketType # | |
| Read SocketType Source # | |
| Defined in Network.Socket.Types Methods readsPrec :: Int -> ReadS SocketType # readList :: ReadS [SocketType] # readPrec :: ReadPrec SocketType # readListPrec :: ReadPrec [SocketType] # | |
| Show SocketType Source # | |
| Defined in Network.Socket.Types Methods showsPrec :: Int -> SocketType -> ShowS # show :: SocketType -> String # showList :: [SocketType] -> ShowS # | |
isSupportedSocketType :: SocketType -> Bool Source #
Does the SOCK_ constant corresponding to the given SocketType exist on this system?
Family
Address families.
A constructor being present here does not mean it is supported by the
 operating system: see isSupportedFamily.
Constructors
isSupportedFamily :: Family -> Bool Source #
Does the AF_ constant corresponding to the given family exist on this system?
Protocol number
type ProtocolNumber = CInt Source #
defaultProtocol :: ProtocolNumber Source #
This is the default protocol for a given service.
Socket address
The existence of a constructor does not necessarily imply that
 that socket address type is supported on your system: see
 isSupportedSockAddr.
Constructors
| SockAddrInet PortNumber HostAddress | |
| SockAddrInet6 PortNumber FlowInfo HostAddress6 ScopeID | |
| SockAddrUnix String | |
| SockAddrCan Int32 | Deprecated: This will be removed in 3.0 | 
isSupportedSockAddr :: SockAddr -> Bool Source #
Is the socket address type supported on this system?
Host address
type HostAddress = Word32 Source #
The raw network byte order number is read using host byte order.
 Therefore on little-endian architectures the byte order is swapped. For
 example 127.0.0.1 is represented as 0x0100007f on little-endian hosts
 and as 0x7f000001 on big-endian hosts.
For direct manipulation prefer hostAddressToTuple and
 tupleToHostAddress.
hostAddressToTuple :: HostAddress -> (Word8, Word8, Word8, Word8) Source #
Converts HostAddress to representation-independent IPv4 quadruple.
 For example for 127.0.0.1 the function will return (0x7f, 0, 0, 1)
 regardless of host endianness.
tupleToHostAddress :: (Word8, Word8, Word8, Word8) -> HostAddress Source #
Converts IPv4 quadruple to HostAddress.
Host address6
type HostAddress6 = (Word32, Word32, Word32, Word32) Source #
Independent of endianness. For example ::1 is stored as (0, 0, 0, 1).
For direct manipulation prefer hostAddress6ToTuple and
 tupleToHostAddress6.
hostAddress6ToTuple :: HostAddress6 -> (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) Source #
tupleToHostAddress6 :: (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> HostAddress6 Source #
Flow Info
Scope ID
ifNameToIndex :: String -> IO (Maybe Int) Source #
Returns the index corresponding to the interface name.
Since 2.7.0.0.
ifIndexToName :: Int -> IO (Maybe String) Source #
Returns the interface name corresponding to the index.
Since 2.7.0.0.
Port number
newtype PortNumber Source #
Use the Num instance (i.e. use a literal) to create a
 PortNumber value with the correct network-byte-ordering. You
 should not use the PortNum constructor. It will be removed in the
 next release.
>>>1 :: PortNumber1>>>read "1" :: PortNumber1
Constructors
| PortNum Word16 | Deprecated: Do not use the PortNum constructor. Use the Num instance. PortNum will be removed in the next release. | 
Instances
socketPortSafe :: Socket -> IO (Maybe PortNumber) Source #
Getting the port of socket.
socketPort :: Socket -> IO PortNumber Source #
Getting the port of socket.
   IOError is thrown if a port is not available.
UNIX-domain socket
isUnixDomainSocketAvailable :: Bool Source #
Whether or not UNIX-domain sockets are available.
Since 3.0.0.0.
socketPair :: Family -> SocketType -> ProtocolNumber -> IO (Socket, Socket) Source #
Build a pair of connected socket objects using the given address
 family, socket type, and protocol number.  Address family, socket
 type, and protocol number are as for the socket function above.
 Availability: Unix.
recvFd :: Socket -> IO CInt Source #
Receive a file descriptor over a domain socket. Note that the resulting
 file descriptor may have to be put into non-blocking mode in order to be
 used safely. See setNonBlockIfNeeded.
getPeerCredential :: Socket -> IO (Maybe CUInt, Maybe CUInt, Maybe CUInt) Source #
Getting process ID, user ID and group ID for UNIX-domain sockets.
This is implemented with SO_PEERCRED on Linux and getpeereid()
   on BSD variants. Unfortunately, on some BSD variants
   getpeereid() returns unexpected results, rather than an error,
   for AF_INET sockets. It is the user's responsibility to make sure
   that the socket is a UNIX-domain socket.
   Also, on some BSD variants, getpeereid() does not return credentials
   for sockets created via socketPair, only separately created and then
   explicitly connected UNIX-domain sockets work on such systems.
Since 2.7.0.0.
Name information
data NameInfoFlag Source #
Flags that control the querying behaviour of getNameInfo.
   For more information, see https://tools.ietf.org/html/rfc3493#page-30
Constructors
| NI_DGRAM | Resolve a datagram-based service name. This is required only for the few protocols that have different port numbers for their datagram-based versions than for their stream-based versions. | 
| NI_NAMEREQD | If the hostname cannot be looked up, an IO error is thrown. | 
| NI_NOFQDN | If a host is local, return only the hostname part of the FQDN. | 
| NI_NUMERICHOST | The name of the host is not looked up. Instead, a numeric representation of the host's address is returned. For an IPv4 address, this will be a dotted-quad string. For IPv6, it will be colon-separated hexadecimal. | 
| NI_NUMERICSERV | The name of the service is not looked up. Instead, a numeric representation of the service is returned. | 
Instances
| Eq NameInfoFlag Source # | |
| Defined in Network.Socket | |
| Read NameInfoFlag Source # | |
| Defined in Network.Socket Methods readsPrec :: Int -> ReadS NameInfoFlag # readList :: ReadS [NameInfoFlag] # | |
| Show NameInfoFlag Source # | |
| Defined in Network.Socket Methods showsPrec :: Int -> NameInfoFlag -> ShowS # show :: NameInfoFlag -> String # showList :: [NameInfoFlag] -> ShowS # | |
Arguments
| :: [NameInfoFlag] | flags to control lookup behaviour | 
| -> Bool | whether to look up a hostname | 
| -> Bool | whether to look up a service name | 
| -> SockAddr | the address to look up | 
| -> IO (Maybe HostName, Maybe ServiceName) | 
Resolve an address to a host or service name.
 This function is protocol independent.
 The list of NameInfoFlag values controls query behaviour.
If a host or service's name cannot be looked up, then the numeric form of the address or service will be returned.
If the query fails, this function throws an IO exception.
Example:
 
   (hostName, _) <- getNameInfo [] True False myAddress
 
Low level operations
setCloseOnExecIfNeeded :: CInt -> IO () Source #
Set the close_on_exec flag on Unix. On Windows, nothing is done.
Since 2.7.0.0.
getCloseOnExec :: CInt -> IO Bool Source #
Get the nonblocking flag.
   On Windows, this function always returns False.
Since 2.7.0.0.
setNonBlockIfNeeded :: CInt -> IO () Source #
Set the nonblocking flag on Unix. On Windows, nothing is done.
getNonBlock :: CInt -> IO Bool Source #
Get the close_on_exec flag.
   On Windows, this function always returns False.
Since 2.7.0.0.
Sending and receiving data
sendBuf :: Socket -> Ptr Word8 -> Int -> IO Int Source #
Send data to the socket. The socket must be connected to a remote socket. Returns the number of bytes sent. Applications are responsible for ensuring that all data has been sent.
Sending data to closed socket may lead to undefined behaviour.
recvBuf :: Socket -> Ptr Word8 -> Int -> IO Int Source #
Receive data from the socket. The socket must be in a connected state. This function may return fewer bytes than specified. If the message is longer than the specified length, it may be discarded depending on the type of socket. This function may block until a message arrives.
Considering hardware and network realities, the maximum number of bytes to receive should be a small power of 2, e.g., 4096.
For TCP sockets, a zero length return value means the peer has closed its half side of the connection.
Receiving data from closed socket may lead to undefined behaviour.
sendBufTo :: Socket -> Ptr a -> Int -> SockAddr -> IO Int Source #
Send data to the socket. The recipient can be specified explicitly, so the socket need not be in a connected state. Returns the number of bytes sent. Applications are responsible for ensuring that all data has been sent.
recvBufFrom :: Socket -> Ptr a -> Int -> IO (Int, SockAddr) Source #
Receive data from the socket, writing it into buffer instead of
 creating a new string.  The socket need not be in a connected
 state. Returns (nbytes, address) where nbytes is the number of
 bytes received and address is a SockAddr representing the
 address of the sending socket.
NOTE: blocking on Windows unless you compile with -threaded (see GHC ticket #1129)
Special constants
maxListenQueue :: Int Source #
This is the value of SOMAXCONN, typically 128. 128 is good enough for normal network servers but is too small for high performance servers.
Deprecated
Deprecated sending and receiving
send :: Socket -> String -> IO Int Source #
Deprecated: Use send defined in Network.Socket.ByteString
Send data to the socket. The socket must be connected to a remote socket. Returns the number of bytes sent. Applications are responsible for ensuring that all data has been sent.
Sending data to closed socket may lead to undefined behaviour.
sendTo :: Socket -> String -> SockAddr -> IO Int Source #
Deprecated: Use sendTo defined in Network.Socket.ByteString
Send data to the socket. The recipient can be specified explicitly, so the socket need not be in a connected state. Returns the number of bytes sent. Applications are responsible for ensuring that all data has been sent.
NOTE: blocking on Windows unless you compile with -threaded (see GHC ticket #1129)
recv :: Socket -> Int -> IO String Source #
Deprecated: Use recv defined in Network.Socket.ByteString
Receive data from the socket. The socket must be in a connected state. This function may return fewer bytes than specified. If the message is longer than the specified length, it may be discarded depending on the type of socket. This function may block until a message arrives.
Considering hardware and network realities, the maximum number of bytes to receive should be a small power of 2, e.g., 4096.
For TCP sockets, a zero length return value means the peer has closed its half side of the connection.
Receiving data from closed socket may lead to undefined behaviour.
recvFrom :: Socket -> Int -> IO (String, Int, SockAddr) Source #
Deprecated: Use recvFrom defined in Network.Socket.ByteString
Receive data from the socket. The socket need not be in a
 connected state. Returns (bytes, nbytes, address) where bytes
 is a String of length nbytes representing the data received and
 address is a SockAddr representing the address of the sending
 socket.
NOTE: blocking on Windows unless you compile with -threaded (see GHC ticket #1129)
recvLen :: Socket -> Int -> IO (String, Int) Source #
Deprecated: Use recv defined in Network.Socket.ByteString with "Data.Bytestring.length"
Deprecated address functions
htonl :: Word32 -> Word32 Source #
Deprecated: Use getAddrInfo instead
Converts the from host byte order to network byte order.
ntohl :: Word32 -> Word32 Source #
Deprecated: Use getAddrInfo instead
Converts the from network byte order to host byte order.
Deprecated socket operations
Deprecated socket status
data SocketStatus Source #
Deprecated: SocketStatus will be removed
The status of the socket as determined by this library, not necessarily reflecting the state of the connection itself.
For example, the Closed status is applied when the close
 function is called.
Constructors
| NotConnected | Newly created, unconnected socket | 
| Bound | Bound, via  | 
| Listening | Listening, via  | 
| Connected | Connected or accepted, via  | 
| ConvertedToHandle | Is now a  | 
| Closed | Closed was closed by  | 
Instances
| Eq SocketStatus Source # | |
| Defined in Network.Socket.Types | |
| Show SocketStatus Source # | |
| Defined in Network.Socket.Types Methods showsPrec :: Int -> SocketStatus -> ShowS # show :: SocketStatus -> String # showList :: [SocketStatus] -> ShowS # | |
Deprecated special constants
aNY_PORT :: PortNumber Source #
Deprecated: Use defaultPort instead
iNADDR_ANY :: HostAddress Source #
Deprecated: Use getAddrInfo instead
The IPv4 wild card address.
iN6ADDR_ANY :: HostAddress6 Source #
Deprecated: Use getAddrInfo instead
The IPv6 wild card address.
sOL_SOCKET :: Int Source #
Deprecated: This is not necessary anymore
sCM_RIGHTS :: Int Source #
Deprecated: This is not necessary anymore
Decrecated internal functions
packFamily :: Family -> CInt Source #
unpackFamily :: CInt -> Family Source #
packSocketType :: SocketType -> CInt Source #
Deprecated: packSocketType will not be available in version 3.0.0.0 or later.
Decrecated UNIX-domain functions
getPeerCred :: Socket -> IO (CUInt, CUInt, CUInt) Source #
Deprecated: Use getPeerCredential instead
Returns the processID, userID and groupID of the socket's peer.
Only available on platforms that support SO_PEERCRED or GETPEEREID(3) on domain sockets. GETPEEREID(3) returns userID and groupID. processID is always 0.