|  | 
| | 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 HostAddress6 = (Word32, Word32, Word32, Word32) |  |  |  | type FlowInfo = Word32 |  |  |  | type ScopeID = Word32 |  |  |  |  |  |  |  | type ProtocolNumber = CInt |  |  |  | defaultProtocol :: ProtocolNumber |  |  |  | newtype  PortNumber  = PortNum Word16 |  |  |  | type HostName = String |  |  |  | type ServiceName = String |  |  |  | data  AddrInfo  = AddrInfo {} |  |  |  |  |  |  |  | addrInfoFlagImplemented :: AddrInfoFlag -> Bool |  |  |  | defaultHints :: AddrInfo |  |  |  | getAddrInfo :: Maybe AddrInfo -> Maybe HostName -> Maybe ServiceName -> IO [AddrInfo] |  |  |  |  |  |  |  | getNameInfo :: [NameInfoFlag] -> Bool -> Bool -> SockAddr -> IO (Maybe HostName, Maybe ServiceName) |  |  |  | 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 |  |  |  | iN6ADDR_ANY :: HostAddress6 |  |  |  | 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 | 
|  | 
|  | 
| | Constructors |  |  |  |  Instances |  |  | 
 | 
|  | 
|  | 
| | 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_ISDN |  |  | 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 |  |  | 
 | 
|  | 
|  | 
| | 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 |  |  | 
 | 
|  | 
|  | 
| | Constructors |  |  |  |  Instances |  |  | 
 | 
|  | 
|  | 
| | Constructors |  | | NotConnected |  |  | Bound |  |  | Listening |  |  | Connected |  |  | ConvertedToHandle |  | 
 |  |  Instances |  |  | 
 | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
| | Constructors |  | | ShutdownReceive |  |  | ShutdownSend |  |  | ShutdownBoth |  | 
 |  |  Instances |  |  | 
 | 
|  | 
|  | 
|  | 
|  | 
| This is the default protocol for a given service. | 
|  | 
|  | 
| | Constructors |  |  |  |  Instances |  |  | 
 | 
|  | 
| Address operations | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
| | Constructors |  |  |  |  Instances |  |  | 
 | 
|  | 
|  | 
| | Flags that control the querying behaviour of getAddrInfo. |  | Constructors |  | | AI_ADDRCONFIG |  |  | AI_ALL |  |  | AI_CANONNAME |  |  | AI_NUMERICHOST |  |  | AI_NUMERICSERV |  |  | AI_PASSIVE |  |  | AI_V4MAPPED |  | 
 |  |  Instances |  |  | 
 | 
|  | 
|  | 
| Indicate whether the given AddrInfoFlag will have any effect on
 this system. | 
|  | 
|  | 
| Default hints for address lookup with getAddrInfo.  The values
 of the addrAddress and addrCanonName fields are undefined,
 and are never inspected by getAddrInfo. | 
|  | 
|  | 
| | :: 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
 bindSocket.
 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:
 
   myHints = defaultHints { addrFlags = [AI_ADDRCONFIG, AI_CANONNAME] }
Values for addrFlags control query behaviour.  The supported
 flags are as follows:
 AI_PASSIVE If no HostName value is provided, the network
     address in each SockAddr
     will be left as a wild card, i.e. as either iNADDR_ANY
     or iN6ADDR_ANY.  This is useful for server applications that
     will accept connections from any client.
AI_CANONNAME The addrCanonName field of the first returned
     AddrInfo will contain the canonical name of the host.
AI_NUMERICHOST The HostName argument must be a numeric
     address in string form, and network name lookups will not be
     attempted.
 Note: Although the following flags are required by RFC 3493, they
 may not have an effect on all platforms, because the underlying
 network stack may not support them.  To see whether a flag from the
 list below will have any effect, call addrInfoFlagImplemented.
 AI_NUMERICSERV The ServiceName argument must be a port
     number in string form, and service name lookups will not be
     attempted.
AI_ADDRCONFIG The list of returned AddrInfo values will
     only contain IPv4 addresses if the local system has at least
     one IPv4 interface configured, and likewise for IPv6.
AI_V4MAPPED If an IPv6 lookup is performed, and no IPv6
     addresses are found, IPv6-mapped IPv4 addresses will be
     returned.
AI_ALL If AI_ALL is specified, return all matching IPv6 and
     IPv4 addresses.  Otherwise, this flag has no effect.
 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.
 Example:
 
   let hints = defaultHints { addrFlags = [AI_ADDRCONFIG, AI_CANONNAME] }
   addrs <- getAddrInfo (Just hints) (Just www.haskell.org) (Just http)
   let addr = head addrs
   sock <- socket (addrFamily addr) (addrSocketType addr) (addrProtocol addr)
   connect sock (addrAddress addr)
 
 | 
 | 
|  | 
|  | 
| | Constructors |  | | NI_DGRAM |  |  | NI_NAMEREQD |  |  | NI_NOFQDN |  |  | NI_NUMERICHOST |  |  | NI_NUMERICSERV |  | 
 |  |  Instances |  |  | 
 | 
|  | 
|  | 
| | :: [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.  The
 supported flags are as follows:
 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.
NI_NAMEREQD If the hostname cannot be looked up, an IO error
     is thrown.
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.
 Hostname and service name lookups can be expensive.  You can
 specify which lookups to perform via the two Bool arguments.  If
 one of these is False, the corresponding value in the returned
 tuple will be Nothing, and no lookup will be performed.
 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
 
 | 
 | 
|  | 
| Socket Operations | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
| Returns the processID, userID and groupID of the socket's peer.
 Only available on platforms that support SO_PEERCRED on domain sockets.
 | 
|  | 
|  | 
|  | 
|  | 
| 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.
 | 
|  | 
|  | 
| NOTE: blocking on Windows unless you compile with -threaded (see
 GHC ticket #1129) | 
|  | 
|  | 
|  | 
|  | 
| NOTE: blocking on Windows unless you compile with -threaded (see
 GHC ticket #1129) | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
| Closes a socket | 
|  | 
| Predicates on sockets | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
| Socket options | 
|  | 
|  | 
| | Constructors |  | | DummySocketOption__ |  |  | Debug |  |  | ReuseAddr |  |  | Type |  |  | SoError |  |  | DontRoute |  |  | Broadcast |  |  | SendBuffer |  |  | RecvBuffer |  |  | KeepAlive |  |  | OOBInline |  |  | TimeToLive |  |  | MaxSegment |  |  | NoDelay |  |  | Linger |  |  | RecvLowWater |  |  | SendLowWater |  |  | RecvTimeOut |  |  | SendTimeOut |  | 
 |  |  Instances |  |  | 
 | 
|  | 
|  | 
|  | 
|  | 
|  | 
| File descriptor transmission | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
| Special Constants | 
|  | 
|  | 
|  | 
|  | 
| The IPv4 wild card address. | 
|  | 
|  | 
| The IPv6 wild card address. | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
| Initialisation | 
|  | 
|  | 
| 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 | 
|  | 
|  | 
|  | 
|  | 
|  | 
| Internal | 
|  | 
| The following are exported ONLY for use in the BSD module and
 should not be used anywhere else. | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
|  | 
| Produced by Haddock version 2.4.2 |