| 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 | Safe-Inferred | 
| Language | Haskell2010 | 
Network.Socket
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
- 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
import Network.Socket.ByteString (recv, sendAll)
main :: IO ()
main = runTCPServer Nothing "3000" talk
  where
    talk s = do
        msg <- recv s 1024
        unless (S.null msg) $ do
          sendAll s msg
          talk s
-- from the "network-run" package.
runTCPServer :: Maybe HostName -> ServiceName -> (Socket -> IO a) -> IO a
runTCPServer mhost port server = withSocketsDo $ do
    addr <- resolve
    E.bracket (open addr) close loop
  where
    resolve = do
        let hints = defaultHints {
                addrFlags = [AI_PASSIVE]
              , addrSocketType = Stream
              }
        head <$> getAddrInfo (Just hints) mhost (Just port)
    open addr = E.bracketOnError (openSocket addr) close $ \sock -> do
        setSocketOption sock ReuseAddr 1
        withFdSocket sock setCloseOnExecIfNeeded
        bind sock $ addrAddress addr
        listen sock 1024
        return sock
    loop sock = forever $ E.bracketOnError (accept sock) (close . fst)
        $ \(conn, _peer) -> void $
            -- 'forkFinally' alone is unlikely to fail thus leaking @conn@,
            -- but 'E.bracketOnError' above will be necessary if some
            -- non-atomic setups (e.g. spawning a subprocess to handle
            -- @conn@) before proper cleanup of @conn@ is your case
            forkFinally (server conn) (const $ gracefulClose conn 5000){-# 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
import Network.Socket.ByteString (recv, sendAll)
main :: IO ()
main = runTCPClient "127.0.0.1" "3000" $ \s -> do
    sendAll s "Hello, world!"
    msg <- recv s 1024
    putStr "Received: "
    C.putStrLn msg
-- from the "network-run" package.
runTCPClient :: HostName -> ServiceName -> (Socket -> IO a) -> IO a
runTCPClient host port client = withSocketsDo $ do
    addr <- resolve
    E.bracket (open addr) close client
  where
    resolve = do
        let hints = defaultHints { addrSocketType = Stream }
        head <$> getAddrInfo (Just hints) (Just host) (Just port)
    open addr = E.bracketOnError (openSocket addr) close $ \sock -> do
        connect sock $ addrAddress addr
        return sockThe 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 ()
- gracefulClose :: Socket -> Int -> IO ()
- shutdown :: Socket -> ShutdownCmd -> IO ()
- data ShutdownCmd
- data SocketOption where- SockOpt CInt CInt
- pattern UnsupportedSocketOption :: SocketOption
- pattern Debug :: SocketOption
- pattern ReuseAddr :: SocketOption
- pattern SoDomain :: SocketOption
- pattern Type :: SocketOption
- pattern SoProtocol :: SocketOption
- pattern SoError :: SocketOption
- pattern DontRoute :: SocketOption
- pattern Broadcast :: SocketOption
- pattern SendBuffer :: SocketOption
- pattern RecvBuffer :: SocketOption
- pattern KeepAlive :: SocketOption
- pattern OOBInline :: SocketOption
- pattern TimeToLive :: SocketOption
- pattern MaxSegment :: SocketOption
- pattern NoDelay :: SocketOption
- pattern Cork :: SocketOption
- pattern Linger :: SocketOption
- pattern ReusePort :: SocketOption
- pattern RecvLowWater :: SocketOption
- pattern SendLowWater :: SocketOption
- pattern RecvTimeOut :: SocketOption
- pattern SendTimeOut :: SocketOption
- pattern UseLoopBack :: SocketOption
- pattern UserTimeout :: SocketOption
- pattern IPv6Only :: SocketOption
- pattern RecvIPv4TTL :: SocketOption
- pattern RecvIPv4TOS :: SocketOption
- pattern RecvIPv4PktInfo :: SocketOption
- pattern RecvIPv6HopLimit :: SocketOption
- pattern RecvIPv6TClass :: SocketOption
- pattern RecvIPv6PktInfo :: SocketOption
 
- data StructLinger = StructLinger {}
- newtype SocketTimeout = SocketTimeout Word32
- isSupportedSocketOption :: SocketOption -> Bool
- whenSupported :: SocketOption -> IO a -> IO ()
- getSocketOption :: Socket -> SocketOption -> IO Int
- setSocketOption :: Socket -> SocketOption -> Int -> IO ()
- getSockOpt :: forall a. Storable a => Socket -> SocketOption -> IO a
- setSockOpt :: Storable a => Socket -> SocketOption -> a -> IO ()
- data Socket
- socket :: Family -> SocketType -> ProtocolNumber -> IO Socket
- openSocket :: AddrInfo -> IO Socket
- withFdSocket :: Socket -> (CInt -> IO r) -> IO r
- unsafeFdSocket :: Socket -> IO CInt
- touchSocket :: Socket -> IO ()
- socketToFd :: Socket -> IO CInt
- fdSocket :: Socket -> IO CInt
- mkSocket :: CInt -> IO Socket
- socketToHandle :: Socket -> IOMode -> IO Handle
- data SocketType where- pattern GeneralSocketType :: CInt -> SocketType
- pattern UnsupportedSocketType :: SocketType
- pattern NoSocketType :: SocketType
- pattern Stream :: SocketType
- pattern Datagram :: SocketType
- pattern Raw :: SocketType
- pattern RDM :: SocketType
- pattern SeqPacket :: SocketType
 
- isSupportedSocketType :: SocketType -> Bool
- getSocketType :: Socket -> IO SocketType
- data Family where- pattern GeneralFamily :: CInt -> Family
- pattern UnsupportedFamily :: Family
- pattern AF_UNSPEC :: Family
- pattern AF_UNIX :: Family
- pattern AF_INET :: Family
- pattern AF_INET6 :: Family
- pattern AF_IMPLINK :: Family
- pattern AF_PUP :: Family
- pattern AF_CHAOS :: Family
- pattern AF_NS :: Family
- pattern AF_NBS :: Family
- pattern AF_ECMA :: Family
- pattern AF_DATAKIT :: Family
- pattern AF_CCITT :: Family
- pattern AF_SNA :: Family
- pattern AF_DECnet :: Family
- pattern AF_DLI :: Family
- pattern AF_LAT :: Family
- pattern AF_HYLINK :: Family
- pattern AF_APPLETALK :: Family
- pattern AF_ROUTE :: Family
- pattern AF_NETBIOS :: Family
- pattern AF_NIT :: Family
- pattern AF_802 :: Family
- pattern AF_ISO :: Family
- pattern AF_OSI :: Family
- pattern AF_NETMAN :: Family
- pattern AF_X25 :: Family
- pattern AF_AX25 :: Family
- pattern AF_OSINET :: Family
- pattern AF_GOSSIP :: Family
- pattern AF_IPX :: Family
- pattern Pseudo_AF_XTP :: Family
- pattern AF_CTF :: Family
- pattern AF_WAN :: Family
- pattern AF_SDL :: Family
- pattern AF_NETWARE :: Family
- pattern AF_NDD :: Family
- pattern AF_INTF :: Family
- pattern AF_COIP :: Family
- pattern AF_CNT :: Family
- pattern Pseudo_AF_RTIP :: Family
- pattern Pseudo_AF_PIP :: Family
- pattern AF_SIP :: Family
- pattern AF_ISDN :: Family
- pattern Pseudo_AF_KEY :: Family
- pattern AF_NATM :: Family
- pattern AF_ARP :: Family
- pattern Pseudo_AF_HDRCMPLT :: Family
- pattern AF_ENCAP :: Family
- pattern AF_LINK :: Family
- pattern AF_RAW :: Family
- pattern AF_RIF :: Family
- pattern AF_NETROM :: Family
- pattern AF_BRIDGE :: Family
- pattern AF_ATMPVC :: Family
- pattern AF_ROSE :: Family
- pattern AF_NETBEUI :: Family
- pattern AF_SECURITY :: Family
- pattern AF_PACKET :: Family
- pattern AF_ASH :: Family
- pattern AF_ECONET :: Family
- pattern AF_ATMSVC :: Family
- pattern AF_IRDA :: Family
- pattern AF_PPPOX :: Family
- pattern AF_WANPIPE :: Family
- pattern AF_BLUETOOTH :: Family
- pattern AF_CAN :: Family
 
- isSupportedFamily :: Family -> Bool
- packFamily :: Family -> CInt
- unpackFamily :: CInt -> Family
- 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)
- data PortNumber
- 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)
- getNameInfo :: [NameInfoFlag] -> Bool -> Bool -> SockAddr -> IO (Maybe HostName, Maybe ServiceName)
- data NameInfoFlag
- 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)
- sendBufMsg :: Socket -> SockAddr -> [(Ptr Word8, Int)] -> [Cmsg] -> MsgFlag -> IO Int
- recvBufMsg :: Socket -> [(Ptr Word8, Int)] -> Int -> MsgFlag -> IO (SockAddr, Int, [Cmsg], MsgFlag)
- data MsgFlag where- pattern MSG_OOB :: MsgFlag
- pattern MSG_DONTROUTE :: MsgFlag
- pattern MSG_PEEK :: MsgFlag
- pattern MSG_EOR :: MsgFlag
- pattern MSG_TRUNC :: MsgFlag
- pattern MSG_CTRUNC :: MsgFlag
- pattern MSG_WAITALL :: MsgFlag
 
- data Cmsg = Cmsg {- cmsgId :: CmsgId
- cmsgData :: ByteString
 
- data CmsgId where- CmsgId CInt CInt
- pattern CmsgIdIPv4TTL :: CmsgId
- pattern CmsgIdIPv6HopLimit :: CmsgId
- pattern CmsgIdIPv4TOS :: CmsgId
- pattern CmsgIdIPv6TClass :: CmsgId
- pattern CmsgIdIPv4PktInfo :: CmsgId
- pattern CmsgIdIPv6PktInfo :: CmsgId
- pattern CmsgIdFds :: CmsgId
- pattern UnsupportedCmsgId :: CmsgId
 
- lookupCmsg :: CmsgId -> [Cmsg] -> Maybe Cmsg
- filterCmsg :: CmsgId -> [Cmsg] -> [Cmsg]
- class ControlMessage a where- controlMessageId :: CmsgId
- encodeCmsg :: a -> Cmsg
- decodeCmsg :: Cmsg -> Maybe a
 
- newtype IPv4TTL = IPv4TTL CInt
- newtype IPv6HopLimit = IPv6HopLimit CInt
- newtype IPv4TOS = IPv4TOS CChar
- newtype IPv6TClass = IPv6TClass CInt
- data IPv4PktInfo = IPv4PktInfo Int HostAddress HostAddress
- data IPv6PktInfo = IPv6PktInfo Int HostAddress6
- maxListenQueue :: Int
- waitReadSocketSTM :: Socket -> IO (STM ())
- waitAndCancelReadSocketSTM :: Socket -> IO (STM (), IO ())
- waitWriteSocketSTM :: Socket -> IO (STM ())
- waitAndCancelWriteSocketSTM :: Socket -> IO (STM (), IO ())
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.
withSocketsDo is not necessary for the current network library.
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 #
Either a service name e.g., "http" or a numeric port number.
Constructors
| AddrInfo | |
| Fields | |
Instances
| Storable AddrInfo Source # | |
| Defined in Network.Socket.Info | |
| Show AddrInfo Source # | |
| Eq AddrInfo Source # | |
defaultHints :: AddrInfo Source #
Default hints for address lookup with 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
| Read AddrInfoFlag Source # | |
| Defined in Network.Socket.Info Methods readsPrec :: Int -> ReadS AddrInfoFlag # readList :: ReadS [AddrInfoFlag] # | |
| Show AddrInfoFlag Source # | |
| Defined in Network.Socket.Info Methods showsPrec :: Int -> AddrInfoFlag -> ShowS # show :: AddrInfoFlag -> String # showList :: [AddrInfoFlag] -> ShowS # | |
| Eq AddrInfoFlag Source # | |
| Defined in Network.Socket.Info | |
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.
 On Unix, FD_CLOEXEC is set to the new Socket.
Closing
close :: Socket -> IO () Source #
Close the socket. This function does not throw exceptions even if the underlying system call returns errors.
If multiple threads use the same socket and one uses unsafeFdSocket and
   the other use close, unexpected behavior may happen.
   For more information, please refer to the documentation of unsafeFdSocket.
close' :: Socket -> IO () Source #
Close the socket. This function throws exceptions if the underlying system call returns errors.
gracefulClose :: Socket -> Int -> IO () Source #
Closing a socket gracefully. This sends TCP FIN and check if TCP FIN is received from the peer. The second argument is time out to receive TCP FIN in millisecond. In both normal cases and error cases, socket is deallocated finally.
Since: 3.1.1.0
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
Bundled Patterns
| pattern UnsupportedSocketOption :: SocketOption | |
| pattern Debug :: SocketOption | SO_DEBUG | 
| pattern ReuseAddr :: SocketOption | SO_REUSEADDR | 
| pattern SoDomain :: SocketOption | SO_DOMAIN, read-only | 
| pattern Type :: SocketOption | SO_TYPE, read-only | 
| pattern SoProtocol :: SocketOption | SO_PROTOCOL, read-only | 
| pattern SoError :: SocketOption | SO_ERROR | 
| pattern DontRoute :: SocketOption | SO_DONTROUTE | 
| pattern Broadcast :: SocketOption | SO_BROADCAST | 
| pattern SendBuffer :: SocketOption | SO_SNDBUF | 
| pattern RecvBuffer :: SocketOption | SO_RCVBUF | 
| pattern KeepAlive :: SocketOption | SO_KEEPALIVE | 
| pattern OOBInline :: SocketOption | SO_OOBINLINE | 
| pattern TimeToLive :: SocketOption | IP_TTL | 
| pattern MaxSegment :: SocketOption | TCP_MAXSEG | 
| pattern NoDelay :: SocketOption | TCP_NODELAY | 
| pattern Cork :: SocketOption | TCP_CORK | 
| pattern Linger :: SocketOption | SO_LINGER: timeout in seconds, 0 means disabling/disabled. | 
| pattern ReusePort :: SocketOption | SO_REUSEPORT | 
| pattern RecvLowWater :: SocketOption | SO_RCVLOWAT | 
| pattern SendLowWater :: SocketOption | SO_SNDLOWAT | 
| pattern RecvTimeOut :: SocketOption | SO_RCVTIMEO: timeout in microseconds. This option is not useful in the normal case where sockets are non-blocking. | 
| pattern SendTimeOut :: SocketOption | SO_SNDTIMEO: timeout in microseconds. This option is not useful in the normal case where sockets are non-blocking. | 
| pattern UseLoopBack :: SocketOption | SO_USELOOPBACK | 
| pattern UserTimeout :: SocketOption | TCP_USER_TIMEOUT | 
| pattern IPv6Only :: SocketOption | IPV6_V6ONLY: don't use this on OpenBSD. | 
| pattern RecvIPv4TTL :: SocketOption | Receiving IPv4 TTL. | 
| pattern RecvIPv4TOS :: SocketOption | Receiving IPv4 TOS. | 
| pattern RecvIPv4PktInfo :: SocketOption | Receiving IP_PKTINFO (struct in_pktinfo). | 
| pattern RecvIPv6HopLimit :: SocketOption | Receiving IPv6 hop limit. | 
| pattern RecvIPv6TClass :: SocketOption | Receiving IPv6 traffic class. | 
| pattern RecvIPv6PktInfo :: SocketOption | Receiving IPV6_PKTINFO (struct in6_pktinfo). | 
Instances
| Read SocketOption Source # | |
| Defined in Network.Socket.Options Methods readsPrec :: Int -> ReadS SocketOption # readList :: ReadS [SocketOption] # | |
| Show SocketOption Source # | |
| Defined in Network.Socket.Options Methods showsPrec :: Int -> SocketOption -> ShowS # show :: SocketOption -> String # showList :: [SocketOption] -> ShowS # | |
| Eq SocketOption Source # | |
| Defined in Network.Socket.Options | |
data StructLinger Source #
Low level SO_LINBER option value, which can be used with setSockOpt.
Constructors
| StructLinger | |
Instances
newtype SocketTimeout Source #
Timeout in microseconds. This will be converted into struct timeval on Unix and DWORD (as milliseconds) on Windows.
Constructors
| SocketTimeout Word32 | 
Instances
isSupportedSocketOption :: SocketOption -> Bool Source #
Does the SocketOption exist on this system?
whenSupported :: SocketOption -> IO a -> IO () Source #
Execute the given action only when the specified socket option is supported. Any return value is ignored.
getSocketOption :: Socket -> SocketOption -> IO Int Source #
Get a socket option that gives an Int value.
setSocketOption :: Socket -> SocketOption -> Int -> IO () Source #
Set a socket option that expects an Int value.
getSockOpt :: forall a. Storable a => Socket -> SocketOption -> IO a Source #
Get a socket option.
setSockOpt :: Storable a => Socket -> SocketOption -> a -> IO () Source #
Set a socket option.
Socket
Basic type for a socket.
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.
>>>import Network.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)>>>Network.Socket.bind sock (addrAddress addr)>>>getSocketName sock127.0.0.1:5000
openSocket :: AddrInfo -> IO Socket Source #
A utility function to open a socket with AddrInfo.
 This is a just wrapper for the following code:
\addr -> socket (addrFamily addr) (addrSocketType addr) (addrProtocol addr)
withFdSocket :: Socket -> (CInt -> IO r) -> IO r Source #
Get a file descriptor from a Socket. The socket will never
 be closed automatically before withFdSocket completes, but
 it may still be closed by an explicit call to close or close',
 either before or during the call.
The file descriptor must not be used after withFdSocket returns, because
 the Socket may have been garbage-collected, invalidating the file
 descriptor.
Since: 3.1.0.0
unsafeFdSocket :: Socket -> IO CInt Source #
Getting a file descriptor from a socket.
If a Socket is shared with multiple threads and
   one uses unsafeFdSocket, unexpected issues may happen.
   Consider the following scenario:
1) Thread A acquires a Fd from Socket by unsafeFdSocket.
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 race condition between unsafeFdSocket and close.
If you use this function, you need to guarantee that the Socket does not
   get garbage-collected until after you finish using the file descriptor.
   touchSocket can be used for this purpose.
A safer option is to use withFdSocket instead.
touchSocket :: Socket -> IO () Source #
Ensure that the given Socket stays alive (i.e. not garbage-collected)
   at the given place in the sequence of IO actions. This function can be
   used in conjunction with unsafeFdSocket to guarantee that the file
   descriptor is not prematurely freed.
fd <- unsafeFdSocket sock -- using fd with blocking operations such as accept(2) touchSocket sock
socketToFd :: Socket -> IO CInt Source #
Socket is closed and a duplicated file descriptor is returned. The duplicated descriptor is no longer subject to the possibility of unexpectedly being closed if the socket is finalized. It is now the caller's responsibility to ultimately close the duplicated file descriptor.
fdSocket :: Socket -> IO CInt Source #
Deprecated: Use withFdSocket or unsafeFdSocket instead
Currently, this is an alias of unsafeFdSocket.
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.
Caveat Handle is not recommended for network programming in
 Haskell, e.g. merely performing hClose on a TCP socket won't
 cooperate with peer's gracefulClose, i.e. proper shutdown
 sequence with appropriate handshakes specified by the protocol.
Types of Socket
data SocketType where Source #
Socket Types.
Some of the defined patterns may be unsupported on some systems:
 see isSupportedSocketType.
Bundled Patterns
| pattern GeneralSocketType :: CInt -> SocketType | Pattern for a general socket type. | 
| pattern UnsupportedSocketType :: SocketType | Unsupported socket type, equal to any other types not supported on this system. | 
| pattern NoSocketType :: SocketType | Used in getAddrInfo hints, for example. | 
| pattern Stream :: SocketType | |
| pattern Datagram :: SocketType | |
| pattern Raw :: SocketType | |
| pattern RDM :: SocketType | |
| pattern SeqPacket :: SocketType | 
Instances
| 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 # | |
| 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 # | |
isSupportedSocketType :: SocketType -> Bool Source #
Is the SOCK_xxxxx constant corresponding to the given SocketType known
 on this system?  GeneralSocketType values, not equal to any of the named
 patterns or UnsupportedSocketType, will return True even when not
 known on this system.
getSocketType :: Socket -> IO SocketType Source #
Get the SocketType of an active socket.
Since: 3.0.1.0
Family
Address families.  The AF_xxxxx constants are widely used as synonyms
 for the corresponding PF_xxxxx protocol family values, to which they are
 numerically equal in mainstream socket API implementations.
Strictly correct usage would be to pass the PF_xxxxx constants as the first
 argument when creating a Socket, while the AF_xxxxx constants should be
 used as addrFamily values with getAddrInfo.  For now only the AF_xxxxx
 constants are provided.
Some of the defined patterns may be unsupported on some systems:
 see isSupportedFamily.
Bundled Patterns
| pattern GeneralFamily :: CInt -> Family | Pattern for a general protocol family (a.k.a. address family). Since: 3.2.0.0 | 
| pattern UnsupportedFamily :: Family | Unsupported address family, equal to any other families that are not supported on the system. Since: 3.2.0.0 | 
| pattern AF_UNSPEC :: Family | unspecified | 
| pattern AF_UNIX :: Family | UNIX-domain | 
| pattern AF_INET :: Family | Internet Protocol version 4 | 
| pattern AF_INET6 :: Family | Internet Protocol version 6 | 
| pattern AF_IMPLINK :: Family | Arpanet imp addresses | 
| pattern AF_PUP :: Family | pup protocols: e.g. BSP | 
| pattern AF_CHAOS :: Family | mit CHAOS protocols | 
| pattern AF_NS :: Family | XEROX NS protocols | 
| pattern AF_NBS :: Family | nbs protocols | 
| pattern AF_ECMA :: Family | european computer manufacturers | 
| pattern AF_DATAKIT :: Family | datakit protocols | 
| pattern AF_CCITT :: Family | CCITT protocols, X.25 etc | 
| pattern AF_SNA :: Family | IBM SNA | 
| pattern AF_DECnet :: Family | DECnet | 
| pattern AF_DLI :: Family | Direct data link interface | 
| pattern AF_LAT :: Family | LAT | 
| pattern AF_HYLINK :: Family | NSC Hyperchannel | 
| pattern AF_APPLETALK :: Family | Apple Talk | 
| pattern AF_ROUTE :: Family | Internal Routing Protocol (aka AF_NETLINK) | 
| pattern AF_NETBIOS :: Family | NetBios-style addresses | 
| pattern AF_NIT :: Family | Network Interface Tap | 
| pattern AF_802 :: Family | IEEE 802.2, also ISO 8802 | 
| pattern AF_ISO :: Family | ISO protocols | 
| pattern AF_OSI :: Family | umbrella of all families used by OSI | 
| pattern AF_NETMAN :: Family | DNA Network Management | 
| pattern AF_X25 :: Family | CCITT X.25 | 
| pattern AF_AX25 :: Family | AX25 | 
| pattern AF_OSINET :: Family | AFI | 
| pattern AF_GOSSIP :: Family | US Government OSI | 
| pattern AF_IPX :: Family | Novell Internet Protocol | 
| pattern Pseudo_AF_XTP :: Family | eXpress Transfer Protocol (no AF) | 
| pattern AF_CTF :: Family | Common Trace Facility | 
| pattern AF_WAN :: Family | Wide Area Network protocols | 
| pattern AF_SDL :: Family | SGI Data Link for DLPI | 
| pattern AF_NETWARE :: Family | Netware | 
| pattern AF_NDD :: Family | NDD | 
| pattern AF_INTF :: Family | Debugging use only | 
| pattern AF_COIP :: Family | connection-oriented IP, aka ST II | 
| pattern AF_CNT :: Family | Computer Network Technology | 
| pattern Pseudo_AF_RTIP :: Family | Help Identify RTIP packets | 
| pattern Pseudo_AF_PIP :: Family | Help Identify PIP packets | 
| pattern AF_SIP :: Family | Simple Internet Protocol | 
| pattern AF_ISDN :: Family | Integrated Services Digital Network | 
| pattern Pseudo_AF_KEY :: Family | Internal key-management function | 
| pattern AF_NATM :: Family | native ATM access | 
| pattern AF_ARP :: Family | ARP (RFC 826) | 
| pattern Pseudo_AF_HDRCMPLT :: Family | Used by BPF to not rewrite hdrs in iface output | 
| pattern AF_ENCAP :: Family | ENCAP | 
| pattern AF_LINK :: Family | Link layer interface | 
| pattern AF_RAW :: Family | Link layer interface | 
| pattern AF_RIF :: Family | raw interface | 
| pattern AF_NETROM :: Family | Amateur radio NetROM | 
| pattern AF_BRIDGE :: Family | multiprotocol bridge | 
| pattern AF_ATMPVC :: Family | ATM PVCs | 
| pattern AF_ROSE :: Family | Amateur Radio X.25 PLP | 
| pattern AF_NETBEUI :: Family | Netbeui 802.2LLC | 
| pattern AF_SECURITY :: Family | Security callback pseudo AF | 
| pattern AF_PACKET :: Family | Packet family | 
| pattern AF_ASH :: Family | Ash | 
| pattern AF_ECONET :: Family | Acorn Econet | 
| pattern AF_ATMSVC :: Family | ATM SVCs | 
| pattern AF_IRDA :: Family | IRDA sockets | 
| pattern AF_PPPOX :: Family | PPPoX sockets | 
| pattern AF_WANPIPE :: Family | Wanpipe API sockets | 
| pattern AF_BLUETOOTH :: Family | bluetooth sockets | 
| pattern AF_CAN :: Family | Controller Area Network | 
isSupportedFamily :: Family -> Bool Source #
Does one of the AF_ constants correspond to a known address family on this
 system.  GeneralFamily values, not equal to any of the named AF_xxxxx
 patterns or UnsupportedFamily, will return True even when not known on
 this system.
packFamily :: Family -> CInt Source #
Protocol number
type ProtocolNumber = CInt Source #
Protocol number.
defaultProtocol :: ProtocolNumber Source #
This is the default protocol for a given service.
>>>defaultProtocol0
Basic socket address type
Socket addresses.
  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 | The path must have fewer than 104 characters. All of these characters must have code points less than 256. | 
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 #
Converts HostAddress6 to representation-independent IPv6 octuple.
tupleToHostAddress6 :: (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> HostAddress6 Source #
Converts IPv6 octuple to HostAddress6.
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
data PortNumber Source #
Port number.
   Use the Num instance (i.e. use a literal) to create a
   PortNumber value.
>>>1 :: PortNumber1>>>read "1" :: PortNumber1>>>show (12345 :: PortNumber)"12345">>>50000 < (51000 :: PortNumber)True>>>50000 < (52000 :: PortNumber)True>>>50000 + (10000 :: PortNumber)60000
Instances
defaultPort :: PortNumber Source #
Default port number.
>>>defaultPort0
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
socketPair :: Family -> SocketType -> ProtocolNumber -> IO (Socket, Socket) Source #
Build a pair of connected socket objects.
   On Windows, this function emulates socketpair() using
   AF_UNIX and a temporary file will remain.
sendFd :: Socket -> CInt -> IO () Source #
Send a file descriptor over a UNIX-domain socket. This function does not work on Windows.
recvFd :: Socket -> IO CInt Source #
Receive a file descriptor over a UNIX-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.
   This function does not work on Windows.
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
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.
>>>addr:_ <- getAddrInfo (Just defaultHints) (Just "127.0.0.1") (Just "http")>>>getNameInfo [NI_NUMERICHOST, NI_NUMERICSERV] True True $ addrAddress addr(Just "127.0.0.1",Just "80")
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
| Read NameInfoFlag Source # | |
| Defined in Network.Socket.Info Methods readsPrec :: Int -> ReadS NameInfoFlag # readList :: ReadS [NameInfoFlag] # | |
| Show NameInfoFlag Source # | |
| Defined in Network.Socket.Info Methods showsPrec :: Int -> NameInfoFlag -> ShowS # show :: NameInfoFlag -> String # showList :: [NameInfoFlag] -> ShowS # | |
| Eq NameInfoFlag Source # | |
| Defined in Network.Socket.Info | |
Low level
socket 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 close_on_exec 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 nonblocking 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.
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.
The return value is the length of received data. Zero means EOF. Historical note: Version 2.8.x.y or earlier, an EOF error was thrown. This was changed in version 3.0.
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.
If the first return value is zero, it means EOF.
For Stream sockets, the second return value would be invalid.
NOTE: blocking on Windows unless you compile with -threaded (see GHC ticket #1129)
Advanced IO
Arguments
| :: Socket | Socket | 
| -> SockAddr | Destination address | 
| -> [(Ptr Word8, Int)] | Data to be sent | 
| -> [Cmsg] | Control messages | 
| -> MsgFlag | Message flags | 
| -> IO Int | The length actually sent | 
Send data to the socket using sendmsg(2).
Arguments
| :: Socket | Socket | 
| -> [(Ptr Word8, Int)] | A list of a pair of buffer and its size.
   If the total length is not large enough,
    | 
| -> Int | The buffer size for control messages.
   If the length is not large enough,
    | 
| -> MsgFlag | Message flags | 
| -> IO (SockAddr, Int, [Cmsg], MsgFlag) | Source address, received data, control messages and message flags | 
Receive data from the socket using recvmsg(2).
Message flags. To combine flags, use (<>).
Bundled Patterns
| pattern MSG_OOB :: MsgFlag | Send or receive OOB(out-of-bound) data. | 
| pattern MSG_DONTROUTE :: MsgFlag | Bypass routing table lookup. | 
| pattern MSG_PEEK :: MsgFlag | Peek at incoming message without removing it from the queue. | 
| pattern MSG_EOR :: MsgFlag | End of record. | 
| pattern MSG_TRUNC :: MsgFlag | Received data is truncated. More data exist. | 
| pattern MSG_CTRUNC :: MsgFlag | Received control message is truncated. More control message exist. | 
| pattern MSG_WAITALL :: MsgFlag | Wait until the requested number of bytes have been read. | 
Instances
| Monoid MsgFlag Source # | |
| Semigroup MsgFlag Source # | |
| Bits MsgFlag Source # | |
| Defined in Network.Socket.Flag Methods (.&.) :: MsgFlag -> MsgFlag -> MsgFlag # (.|.) :: MsgFlag -> MsgFlag -> MsgFlag # xor :: MsgFlag -> MsgFlag -> MsgFlag # complement :: MsgFlag -> MsgFlag # shift :: MsgFlag -> Int -> MsgFlag # rotate :: MsgFlag -> Int -> MsgFlag # setBit :: MsgFlag -> Int -> MsgFlag # clearBit :: MsgFlag -> Int -> MsgFlag # complementBit :: MsgFlag -> Int -> MsgFlag # testBit :: MsgFlag -> Int -> Bool # bitSizeMaybe :: MsgFlag -> Maybe Int # shiftL :: MsgFlag -> Int -> MsgFlag # unsafeShiftL :: MsgFlag -> Int -> MsgFlag # shiftR :: MsgFlag -> Int -> MsgFlag # unsafeShiftR :: MsgFlag -> Int -> MsgFlag # rotateL :: MsgFlag -> Int -> MsgFlag # | |
| Num MsgFlag Source # | |
| Show MsgFlag Source # | |
| Eq MsgFlag Source # | |
| Ord MsgFlag Source # | |
Control message (ancillary data)
Control message (ancillary data) including a pair of level and type.
Constructors
| Cmsg | |
| Fields 
 | |
Identifier of control message (ancillary data).
Bundled Patterns
| pattern CmsgIdIPv4TTL :: CmsgId | The identifier for  | 
| pattern CmsgIdIPv6HopLimit :: CmsgId | The identifier for  | 
| pattern CmsgIdIPv4TOS :: CmsgId | The identifier for  | 
| pattern CmsgIdIPv6TClass :: CmsgId | The identifier for  | 
| pattern CmsgIdIPv4PktInfo :: CmsgId | The identifier for  | 
| pattern CmsgIdIPv6PktInfo :: CmsgId | The identifier for  | 
| pattern CmsgIdFds :: CmsgId | The identifier for  | 
| pattern UnsupportedCmsgId :: CmsgId | Unsupported identifier | 
APIs for control message
lookupCmsg :: CmsgId -> [Cmsg] -> Maybe Cmsg Source #
Locate a control message of the given type in a list of control messages. The following shows an example usage:
(lookupCmsg CmsgIdIPv4TOS cmsgs >>= decodeCmsg) :: Maybe IPv4TOS
Class and types for control message
class ControlMessage a where Source #
Control message type class.
   Each control message type has a numeric CmsgId and encode
   and decode functions.
Methods
controlMessageId :: CmsgId Source #
encodeCmsg :: a -> Cmsg Source #
decodeCmsg :: Cmsg -> Maybe a Source #
Instances
Time to live of IPv4.
Instances
| Storable IPv4TTL Source # | |
| Show IPv4TTL Source # | |
| Eq IPv4TTL Source # | |
| ControlMessage IPv4TTL Source # | |
| Defined in Network.Socket.Posix.Cmsg | |
newtype IPv6HopLimit Source #
Hop limit of IPv6.
Constructors
| IPv6HopLimit CInt | 
Instances
| Storable IPv6HopLimit Source # | |
| Defined in Network.Socket.Posix.Cmsg Methods sizeOf :: IPv6HopLimit -> Int # alignment :: IPv6HopLimit -> Int # peekElemOff :: Ptr IPv6HopLimit -> Int -> IO IPv6HopLimit # pokeElemOff :: Ptr IPv6HopLimit -> Int -> IPv6HopLimit -> IO () # peekByteOff :: Ptr b -> Int -> IO IPv6HopLimit # pokeByteOff :: Ptr b -> Int -> IPv6HopLimit -> IO () # peek :: Ptr IPv6HopLimit -> IO IPv6HopLimit # poke :: Ptr IPv6HopLimit -> IPv6HopLimit -> IO () # | |
| Show IPv6HopLimit Source # | |
| Defined in Network.Socket.Posix.Cmsg Methods showsPrec :: Int -> IPv6HopLimit -> ShowS # show :: IPv6HopLimit -> String # showList :: [IPv6HopLimit] -> ShowS # | |
| Eq IPv6HopLimit Source # | |
| Defined in Network.Socket.Posix.Cmsg | |
| ControlMessage IPv6HopLimit Source # | |
| Defined in Network.Socket.Posix.Cmsg Methods controlMessageId :: CmsgId Source # encodeCmsg :: IPv6HopLimit -> Cmsg Source # decodeCmsg :: Cmsg -> Maybe IPv6HopLimit Source # | |
TOS of IPv4.
Instances
| Storable IPv4TOS Source # | |
| Show IPv4TOS Source # | |
| Eq IPv4TOS Source # | |
| ControlMessage IPv4TOS Source # | |
| Defined in Network.Socket.Posix.Cmsg | |
newtype IPv6TClass Source #
Traffic class of IPv6.
Constructors
| IPv6TClass CInt | 
Instances
| Storable IPv6TClass Source # | |
| Defined in Network.Socket.Posix.Cmsg Methods sizeOf :: IPv6TClass -> Int # alignment :: IPv6TClass -> Int # peekElemOff :: Ptr IPv6TClass -> Int -> IO IPv6TClass # pokeElemOff :: Ptr IPv6TClass -> Int -> IPv6TClass -> IO () # peekByteOff :: Ptr b -> Int -> IO IPv6TClass # pokeByteOff :: Ptr b -> Int -> IPv6TClass -> IO () # peek :: Ptr IPv6TClass -> IO IPv6TClass # poke :: Ptr IPv6TClass -> IPv6TClass -> IO () # | |
| Show IPv6TClass Source # | |
| Defined in Network.Socket.Posix.Cmsg Methods showsPrec :: Int -> IPv6TClass -> ShowS # show :: IPv6TClass -> String # showList :: [IPv6TClass] -> ShowS # | |
| Eq IPv6TClass Source # | |
| Defined in Network.Socket.Posix.Cmsg | |
| ControlMessage IPv6TClass Source # | |
| Defined in Network.Socket.Posix.Cmsg Methods controlMessageId :: CmsgId Source # encodeCmsg :: IPv6TClass -> Cmsg Source # decodeCmsg :: Cmsg -> Maybe IPv6TClass Source # | |
data IPv4PktInfo Source #
Network interface ID and local IPv4 address.
Constructors
| IPv4PktInfo Int HostAddress HostAddress | 
Instances
| Storable IPv4PktInfo Source # | |
| Defined in Network.Socket.Posix.Cmsg Methods sizeOf :: IPv4PktInfo -> Int # alignment :: IPv4PktInfo -> Int # peekElemOff :: Ptr IPv4PktInfo -> Int -> IO IPv4PktInfo # pokeElemOff :: Ptr IPv4PktInfo -> Int -> IPv4PktInfo -> IO () # peekByteOff :: Ptr b -> Int -> IO IPv4PktInfo # pokeByteOff :: Ptr b -> Int -> IPv4PktInfo -> IO () # peek :: Ptr IPv4PktInfo -> IO IPv4PktInfo # poke :: Ptr IPv4PktInfo -> IPv4PktInfo -> IO () # | |
| Show IPv4PktInfo Source # | |
| Defined in Network.Socket.Posix.Cmsg Methods showsPrec :: Int -> IPv4PktInfo -> ShowS # show :: IPv4PktInfo -> String # showList :: [IPv4PktInfo] -> ShowS # | |
| Eq IPv4PktInfo Source # | |
| Defined in Network.Socket.Posix.Cmsg | |
| ControlMessage IPv4PktInfo Source # | |
| Defined in Network.Socket.Posix.Cmsg Methods controlMessageId :: CmsgId Source # encodeCmsg :: IPv4PktInfo -> Cmsg Source # decodeCmsg :: Cmsg -> Maybe IPv4PktInfo Source # | |
data IPv6PktInfo Source #
Network interface ID and local IPv4 address.
Constructors
| IPv6PktInfo Int HostAddress6 | 
Instances
| Storable IPv6PktInfo Source # | |
| Defined in Network.Socket.Posix.Cmsg Methods sizeOf :: IPv6PktInfo -> Int # alignment :: IPv6PktInfo -> Int # peekElemOff :: Ptr IPv6PktInfo -> Int -> IO IPv6PktInfo # pokeElemOff :: Ptr IPv6PktInfo -> Int -> IPv6PktInfo -> IO () # peekByteOff :: Ptr b -> Int -> IO IPv6PktInfo # pokeByteOff :: Ptr b -> Int -> IPv6PktInfo -> IO () # peek :: Ptr IPv6PktInfo -> IO IPv6PktInfo # poke :: Ptr IPv6PktInfo -> IPv6PktInfo -> IO () # | |
| Show IPv6PktInfo Source # | |
| Defined in Network.Socket.Posix.Cmsg Methods showsPrec :: Int -> IPv6PktInfo -> ShowS # show :: IPv6PktInfo -> String # showList :: [IPv6PktInfo] -> ShowS # | |
| Eq IPv6PktInfo Source # | |
| Defined in Network.Socket.Posix.Cmsg | |
| ControlMessage IPv6PktInfo Source # | |
| Defined in Network.Socket.Posix.Cmsg Methods controlMessageId :: CmsgId Source # encodeCmsg :: IPv6PktInfo -> Cmsg Source # decodeCmsg :: Cmsg -> Maybe IPv6PktInfo Source # | |
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.
STM to check read and write
waitReadSocketSTM :: Socket -> IO (STM ()) Source #
STM action to wait until the socket is ready for reading.
waitAndCancelReadSocketSTM :: Socket -> IO (STM (), IO ()) Source #
STM action to wait until the socket is ready for reading and STM action to cancel the waiting.