socket-0.8.3.0: An extensible socket library.

Copyright(c) Lars Petersen 2015
LicenseMIT
Maintainerinfo@lars-petersen.net
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

System.Socket

Contents

Description

{-# LANGUAGE OverloadedStrings #-}
module Main where

import Control.Exception ( bracket, catch )
import Control.Monad ( forever )

import System.Socket
import System.Socket.Family.Inet6
import System.Socket.Type.Stream
import System.Socket.Protocol.TCP

main :: IO ()
main = bracket
  ( socket :: IO (Socket Inet6 Stream TCP) )
  ( \s-> do
    close s
    putStrLn "Listening socket closed."
  )
  ( \s-> do
    setSocketOption s (ReuseAddress True)
    setSocketOption s (V6Only False)
    bind s (SocketAddressInet6 inet6Any 8080 0 0)
    listen s 5
    putStrLn "Listening socket ready..."
    forever $ acceptAndHandle s `catch` \e-> print (e :: SocketException)
  )

acceptAndHandle :: Socket Inet6 Stream TCP -> IO ()
acceptAndHandle s = bracket
  ( accept s )
  ( \(p, addr)-> do
    close p
    putStrLn $ "Closed connection to " ++ show addr
  )
  ( \(p, addr)-> do
    putStrLn $ "Accepted connection from " ++ show addr
    sendAll p "Hello world!" msgNoSignal
  )
Synopsis

Socket

data Socket f t p Source #

A generic socket type. Use socket to create a new socket.

The socket is just an MVar-wrapped file descriptor. The Socket constructor is exported trough the unsafe module in order to make this library easily extensible, but it is usually not necessary nor advised to work directly on the file descriptor. If you do, the following rules must be obeyed:

  • Make sure not to deadlock. Use withMVar or similar.
  • The lock must not be held during a blocking call. This would make it impossible to send and receive simultaneously or to close the socket.
  • The lock must be held when calling operations that use the file descriptor. Otherwise the socket might get closed or even reused by another thread/capability which might result in reading from or writing on a totally different socket. This is a security nightmare!
  • The socket is non-blocking and all the code relies on that assumption. You need to use GHC's eventing mechanism primitives to block until something happens. The former rules forbid to use threadWaitRead as it does not separate between registering the file descriptor (for which the lock must be held) and the actual waiting (for which you must not hold the lock). Also see this thread and read the library code to see how the problem is currently circumvented.

Family

class Storable (SocketAddress f) => Family f where Source #

The address Family determines the network protocol to use.

The most common address families are Inet (IPv4) and Inet6 (IPv6).

Associated Types

data SocketAddress f Source #

The SocketAddress type is a data family. This allows to provide different data constructors depending on the socket family without knowing all of them in advance or the need to extend this core library.

SocketAddressInet  inetLoopback  8080     :: SocketAddress Inet
SocketAddressInet6 inet6Loopback 8080 0 0 :: SocketAddress Inet6

Methods

familyNumber :: f -> CInt Source #

The number designating this Family on the specific platform. This method is only exported for implementing extension libraries.

This function shall yield the values of constants like AF_INET, AF_INET6 etc.

Instances
Family Inet Source # 
Instance details

Defined in System.Socket.Family.Inet

Associated Types

data SocketAddress Inet :: Type Source #

Family Inet6 Source # 
Instance details

Defined in System.Socket.Family.Inet6

Associated Types

data SocketAddress Inet6 :: Type Source #

Type

class Type t where Source #

The Type determines properties of the transport layer and the semantics of basic socket operations.

The instances supplied by this library are Raw (no transport layer), Stream (for unframed binary streams, e.g. TCP), Datagram (for datagrams of limited length, e.g. UDP) and SequentialPacket (for framed messages of arbitrary length, e.g. SCTP).

Methods

typeNumber :: t -> CInt Source #

This number designates this Type on the specific platform. This method is only exported for implementing extension libraries.

The function shall yield the values of constants like SOCK_STREAM, SOCK_DGRAM etc.

Instances
Type Datagram Source # 
Instance details

Defined in System.Socket.Type.Datagram

Type Raw Source # 
Instance details

Defined in System.Socket.Type.Raw

Methods

typeNumber :: Raw -> CInt Source #

Type SequentialPacket Source # 
Instance details

Defined in System.Socket.Type.SequentialPacket

Type Stream Source # 
Instance details

Defined in System.Socket.Type.Stream

Protocol

class Protocol p where Source #

The Protocol determines the transport protocol to use.

Use Default to let the operating system choose a transport protocol compatible with the socket's Type.

Methods

protocolNumber :: p -> CInt Source #

This number designates this Protocol on the specific platform. This method is only exported for implementing extension libraries.

The function shall yield the values of constants like IPPROTO_TCP, IPPROTO_UDP etc.

Instances
Protocol Default Source # 
Instance details

Defined in System.Socket.Protocol.Default

Protocol TCP Source # 
Instance details

Defined in System.Socket.Protocol.TCP

Protocol UDP Source # 
Instance details

Defined in System.Socket.Protocol.UDP

Operations

socket

socket :: (Family f, Type t, Protocol p) => IO (Socket f t p) Source #

Creates a new socket.

Whereas the underlying POSIX socket operation takes 3 parameters, this library encodes this information in the type variables. This rules out several kinds of errors and especially simplifies the handling of addresses (by using associated data families). Examples:

-- create an IPv4-UDP-datagram socket
sock <- socket :: IO (Socket Inet Datagram UDP)
-- create an IPv6-TCP-streaming socket
sock6 <- socket :: IO (Socket Inet6 Stream TCP)
-- create an IPv6-streaming socket with default protocol (usually TCP)
sock6 <- socket :: IO (Socket Inet6 Strem Default)
  • This operation sets up a finalizer that automatically closes the socket when the garbage collection decides to collect it. This is just a fail-safe. You might still run out of file descriptors as there's no guarantee about when the finalizer is run. You're advised to manually close the socket when it's no longer needed. If possible, use bracket to reliably close the socket descriptor on exception or regular termination of your computation:
result <- bracket (socket :: IO (Socket Inet6 Stream TCP)) close $ \sock-> do
  somethingWith sock -- your computation here
  return somethingelse
  • This operation configures the socket non-blocking to work seamlessly with the runtime system's event notification mechanism.
  • This operation can safely deal with asynchronous exceptions without leaking file descriptors.
  • This operation throws SocketExceptions. Consult your man socket for details and specific errors.

connect

connect :: Family f => Socket f t p -> SocketAddress f -> IO () Source #

Connects to a remote address.

  • This operation returns as soon as a connection has been established (as if the socket were blocking). The connection attempt has either failed or succeeded after this operation threw an exception or returned.
  • The operation throws SocketExceptions. Calling connect on a closed socket throws eBadFileDescriptor even if the former file descriptor has been reassigned.

bind

bind :: Family f => Socket f t p -> SocketAddress f -> IO () Source #

Bind a socket to an address.

  • Calling bind on a closed socket throws eBadFileDescriptor even if the former file descriptor has been reassigned.
  • It is assumed that bind never blocks and therefore eInProgress, eAlready and eInterrupted don't occur. This assumption is supported by the fact that the Linux manpage doesn't mention any of these errors, the Posix manpage doesn't mention the last one and even MacOS' implementation will never fail with any of these when the socket is configured non-blocking as argued here.
  • This operation throws SocketExceptions. Consult your man page for details and specific errnos.

listen

listen :: Socket f t p -> Int -> IO () Source #

Starts listening and queueing connection requests on a connection-mode socket. The second parameter determines the backlog size.

  • Calling listen on a closed socket throws eBadFileDescriptor even if the former file descriptor has been reassigned.
  • The second parameter is called backlog and sets a limit on how many unaccepted connections the transport implementation shall queue. A value of 0 leaves the decision to the implementation.
  • This operation throws SocketExceptions. Consult your man listen for details and specific errors.

accept

accept :: Family f => Socket f t p -> IO (Socket f t p, SocketAddress f) Source #

Accept a new connection.

  • Calling accept on a closed socket throws eBadFileDescriptor even if the former file descriptor has been reassigned.
  • This operation configures the new socket non-blocking. It uses accept4 (when available) in order to accept and set the socket non-blocking with a single system call.
  • This operation sets up a finalizer for the new socket that automatically closes the new socket when the garbage collection decides to collect it. This is just a fail-safe. You might still run out of file descriptors as there's no guarantee about when the finalizer is run. You're advised to manually close the socket when it's no longer needed.
  • This operation throws SocketExceptions.
  • This operation catches eAgain, eWouldBlock and eInterrupted internally and retries automatically.

send, sendTo

send :: Socket f t p -> ByteString -> MessageFlags -> IO Int Source #

Send data.

sendTo :: Family f => Socket f t p -> ByteString -> MessageFlags -> SocketAddress f -> IO Int Source #

Like send, but allows to specify a destination address.

receive, receiveFrom

receive :: Socket f t p -> Int -> MessageFlags -> IO ByteString Source #

Receive data.

  • The operation takes a buffer size in bytes a first parameter which limits the maximum length of the returned ByteString.
  • When an empty ByteString is returned this usally (protocol specific) means that the peer gracefully closed the connection. The user is advised to check for and handle this case.
  • Calling receive on a closed socket throws eBadFileDescriptor even if the former file descriptor has been reassigned.
  • This operation throws SocketExceptions. Consult man recv for details and specific errors.
  • eAgain, eWouldBlock and eInterrupted and handled internally and won't be thrown. For performance reasons the operation first tries a read on the socket and then waits when it got eAgain or eWouldBlock until the socket is signaled to be readable.

receiveFrom :: Family f => Socket f t p -> Int -> MessageFlags -> IO (ByteString, SocketAddress f) Source #

Like receive, but additionally yields the peer address.

close

close :: Socket f t p -> IO () Source #

Closes a socket.

  • This operation is idempotent and thus can be performed more than once without throwing an exception. If it throws an exception it is presumably a not recoverable situation and the process should exit.
  • This operation does not block.
  • This operation wakes up all threads that are currently blocking on this socket. All other threads are guaranteed to not block on operations on this socket in the future. Threads that perform operations other than close on this socket will fail with eBadFileDescriptor after the socket has been closed (close replaces the Fd in the MVar with -1 to reliably avoid use-after-free situations).
  • This operation potentially throws SocketExceptions (only EIO is documented). eInterrupted is catched internally and retried automatically, so won't be thrown.

Name Resolution

getAddress

getAddress :: Family f => Socket f t p -> IO (SocketAddress f) Source #

Get a socket's (local) address.

> (socket :: IO (Socket Inet Stream TCP)) >>= getAddress
SocketAddressInet {inetAddress = InetAddress 0.0.0.0, inetPort = InetPort 0}

getAddressInfo

data AddressInfo f t p Source #

Instances
Eq (SocketAddress f) => Eq (AddressInfo f t p) Source # 
Instance details

Defined in System.Socket.Internal.AddressInfo

Methods

(==) :: AddressInfo f t p -> AddressInfo f t p -> Bool #

(/=) :: AddressInfo f t p -> AddressInfo f t p -> Bool #

Show (SocketAddress f) => Show (AddressInfo f t p) Source # 
Instance details

Defined in System.Socket.Internal.AddressInfo

Methods

showsPrec :: Int -> AddressInfo f t p -> ShowS #

show :: AddressInfo f t p -> String #

showList :: [AddressInfo f t p] -> ShowS #

class Family f => HasAddressInfo f where Source #

This class is for address families that support name resolution.

Methods

getAddressInfo :: (Type t, Protocol p) => Maybe ByteString -> Maybe ByteString -> AddressInfoFlags -> IO [AddressInfo f t p] Source #

Maps names to addresses (i.e. by DNS lookup).

The operation throws AddressInfoExceptions.

Contrary to the underlying getaddrinfo operation this wrapper is typesafe and thus only returns records that match the address, type and protocol encoded in the type. This is the price we have to pay for typesafe sockets and extensibility.

If you need different types of records, you need to start several queries. If you want to connect to both IPv4 and IPV6 addresses use aiV4Mapped and use IPv6-sockets.

getAddressInfo (Just "www.haskell.org") (Just "https") mempty :: IO [AddressInfo Inet Stream TCP]
> [AddressInfo {addressInfoFlags = AddressInfoFlags 0, socketAddress = SocketAddressInet {inetAddress = InetAddress 162.242.239.16, inetPort = InetPort 443}, canonicalName = Nothing}]
> getAddressInfo (Just "www.haskell.org") (Just "80") aiV4Mapped :: IO [AddressInfo Inet6 Stream TCP]
[AddressInfo {
   addressInfoFlags = AddressInfoFlags 8,
   socketAddress    = SocketAddressInet6 {inet6Address = Inet6Address 2400:cb00:2048:0001:0000:0000:6ca2:cc3c, inet6Port = Inet6Port 80, inet6FlowInfo = Inet6FlowInfo 0, inet6ScopeId = Inet6ScopeId 0},
   canonicalName    = Nothing }]
> getAddressInfo (Just "darcs.haskell.org") Nothing aiV4Mapped :: IO [AddressInfo Inet6 Stream TCP]
[AddressInfo {
   addressInfoFlags = AddressInfoFlags 8,
   socketAddress    = SocketAddressInet6 {inet6Address = Inet6Address 0000:0000:0000:0000:0000:ffff:17fd:e1ad, inet6Port = Inet6Port 0, inet6FlowInfo = Inet6FlowInfo 0, inet6ScopeId = Inet6ScopeId 0},
   canonicalName    = Nothing }]
> getAddressInfo (Just "darcs.haskell.org") Nothing mempty :: IO [AddressInfo Inet6 Stream TCP]
*** Exception: AddressInfoException "Name or service not known"

getNameInfo

data NameInfo Source #

A NameInfo consists of host and service name.

Constructors

NameInfo 
Instances
Eq NameInfo Source # 
Instance details

Defined in System.Socket.Internal.AddressInfo

Show NameInfo Source # 
Instance details

Defined in System.Socket.Internal.AddressInfo

class Family f => HasNameInfo f where Source #

This class is for address families that support reverse name resolution.

Methods

getNameInfo :: SocketAddress f -> NameInfoFlags -> IO NameInfo Source #

(Reverse-)map an address back to a human-readable host- and service name.

The operation throws AddressInfoExceptions.

> getNameInfo (SocketAddressInet inetLoopback 80) mempty
NameInfo {hostName = "localhost.localdomain", serviceName = "http"}

Options

class SocketOption o where Source #

SocketOptions allow to read and write certain properties of a socket.

Methods

getSocketOption :: Socket f t p -> IO o Source #

Get a specific SocketOption.

  • This operation throws SocketExceptions. Consult man getsockopt for details and specific errors.

setSocketOption :: Socket f t p -> o -> IO () Source #

Set a specific SocketOption.

  • This operation throws SocketExceptions. Consult man setsockopt for details and specific errors.

Error

data Error Source #

Reports the last error that occured on the socket.

  • Also known as SO_ERROR.
  • The operation setSocketOption always throws eInvalid for this option.
  • Use with care in the presence of concurrency!

Constructors

Error SocketException 
Instances
Eq Error Source # 
Instance details

Defined in System.Socket.Internal.SocketOption

Methods

(==) :: Error -> Error -> Bool #

(/=) :: Error -> Error -> Bool #

Ord Error Source # 
Instance details

Defined in System.Socket.Internal.SocketOption

Methods

compare :: Error -> Error -> Ordering #

(<) :: Error -> Error -> Bool #

(<=) :: Error -> Error -> Bool #

(>) :: Error -> Error -> Bool #

(>=) :: Error -> Error -> Bool #

max :: Error -> Error -> Error #

min :: Error -> Error -> Error #

Show Error Source # 
Instance details

Defined in System.Socket.Internal.SocketOption

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

SocketOption Error Source # 
Instance details

Defined in System.Socket.Internal.SocketOption

Methods

getSocketOption :: Socket f t p -> IO Error Source #

setSocketOption :: Socket f t p -> Error -> IO () Source #

ReuseAddress

data ReuseAddress Source #

Allows or disallows the reuse of a local address in a bind call.

  • Also known as SO_REUSEADDR.
  • This is particularly useful when experiencing eAddressInUse exceptions.

Constructors

ReuseAddress Bool 

KeepAlive

data KeepAlive Source #

When enabled the protocol checks in a protocol-specific manner if the other end is still alive.

  • Also known as SO_KEEPALIVE.

Constructors

KeepAlive Bool 

Flags

MessageFlags

newtype MessageFlags Source #

Use the Monoid instance to combine several flags:

mconcat [msgNoSignal, msgWaitAll]

Use the Bits instance to check whether a flag is set:

if flags .&. msgEndOfRecord /= mempty then ...

Constructors

MessageFlags CInt 
Instances
Eq MessageFlags Source # 
Instance details

Defined in System.Socket.Internal.Message

Show MessageFlags Source # 
Instance details

Defined in System.Socket.Internal.Message

Semigroup MessageFlags Source # 
Instance details

Defined in System.Socket.Internal.Message

Monoid MessageFlags Source # 
Instance details

Defined in System.Socket.Internal.Message

Storable MessageFlags Source # 
Instance details

Defined in System.Socket.Internal.Message

Bits MessageFlags Source # 
Instance details

Defined in System.Socket.Internal.Message

msgNoSignal :: MessageFlags Source #

MSG_NOSIGNAL

Suppresses the generation of PIPE signals when writing to a socket that is no longer connected.

Although this flag is POSIX, it is not available on all platforms. Try

msgNoSignal /= mempty

in order to check whether this flag is defined on a certain platform. It is safe to just use this constant even if it might not have effect on a certain target platform. The platform independence of this flag is therefore fulfilled to some extent.

Some more explanation on the platform specific behaviour:

  • Linux defines and supports MSG_NOSIGNAL and properly suppresses the generation of broken pipe-related signals.
  • Windows does not define it, but does not generate signals either.
  • OSX does not define it, but generates PIPE signals. The GHC runtime ignores them if you don't hook them explicitly. The non-portable socket option SO_NOSIGPIPE may be used disable signals on a per-socket basis.

It is safe and advised to always use this flag unless one wants to explictly hook and handle the PIPE signal which is not very useful in todays multi-threaded environments anyway. Although GHC's RTS ignores the signal by default it causes an unnecessary interruption.

msgEndOfRecord :: MessageFlags Source #

Warning: Untested: Use at your own risk!

MSG_EOR

Used by SequentialPacket to mark record boundaries. Consult the POSIX standard for details.

msgOutOfBand :: MessageFlags Source #

Warning: Untested: Use at your own risk!

MSG_OOB

Used to send and receive out-of-band data. Consult the relevant standards for details.

msgWaitAll :: MessageFlags Source #

Warning: Untested: Use at your own risk!

MSG_WAITALL

A receive call shall not return unless the requested number of bytes becomes available.

msgPeek :: MessageFlags Source #

MSG_PEEK

A receive shall not actually remove the received data from the input buffer.

AddressInfoFlags

data AddressInfoFlags Source #

Use the Monoid instance to combine several flags:

mconcat [aiAddressConfig, aiV4Mapped]
Instances
Eq AddressInfoFlags Source # 
Instance details

Defined in System.Socket.Internal.AddressInfo

Show AddressInfoFlags Source # 
Instance details

Defined in System.Socket.Internal.AddressInfo

Semigroup AddressInfoFlags Source # 
Instance details

Defined in System.Socket.Internal.AddressInfo

Monoid AddressInfoFlags Source # 
Instance details

Defined in System.Socket.Internal.AddressInfo

Bits AddressInfoFlags Source # 
Instance details

Defined in System.Socket.Internal.AddressInfo

aiAll :: AddressInfoFlags Source #

AI_ALL: Return both IPv4 (as v4-mapped IPv6 address) and IPv6 addresses when aiV4Mapped is set independent of whether IPv6 addresses exist for this name.

aiV4Mapped :: AddressInfoFlags Source #

AI_V4MAPPED: Return mapped IPv4 addresses if no IPv6 addresses could be found or if aiAll flag is set.

NameInfoFlags

data NameInfoFlags Source #

Use the Monoid instance to combine several flags:

mconcat [niNameRequired, niNoFullyQualifiedDomainName]
Instances
Eq NameInfoFlags Source # 
Instance details

Defined in System.Socket.Internal.AddressInfo

Show NameInfoFlags Source # 
Instance details

Defined in System.Socket.Internal.AddressInfo

Semigroup NameInfoFlags Source # 
Instance details

Defined in System.Socket.Internal.AddressInfo

Monoid NameInfoFlags Source # 
Instance details

Defined in System.Socket.Internal.AddressInfo

Bits NameInfoFlags Source # 
Instance details

Defined in System.Socket.Internal.AddressInfo

niNameRequired :: NameInfoFlags Source #

NI_NAMEREQD: Throw an exception if the hostname cannot be determined.

niDatagram :: NameInfoFlags Source #

NI_DGRAM: Service is datagram based (i.e. UDP) rather than stream based (i.e. TCP).

niNoFullyQualifiedDomainName :: NameInfoFlags Source #

NI_NOFQDN: Return only the hostname part of the fully qualified domain name for local hosts.

niNumericHost :: NameInfoFlags Source #

NI_NUMERICHOST: Return the numeric form of the host address.

niNumericService :: NameInfoFlags Source #

NI_NUMERICSERV: Return the numeric form of the service address.

Exceptions

SocketException

newtype SocketException Source #

Contains the error code that can be matched against.

Hint: Use guards or MultiWayIf to match against specific exceptions:

if | e == eAddressInUse -> ...
   | e == eAddressNotAvailable -> ...
   | otherwise -> ...

Constructors

SocketException CInt 

eInterrupted :: SocketException Source #

Interrupted system call.

NOTE: This exception shall not be thrown by any public operation in this library, but is handled internally.

eInvalid :: SocketException Source #

Invalid argument.

ePipe :: SocketException Source #

Broken pipe.

eWouldBlock :: SocketException Source #

Resource temporarily unavailable.

NOTE: This exception shall not be thrown by any public operation in this library, but is handled internally.

eAgain :: SocketException Source #

Resource temporarily unavailable.

eNotSocket :: SocketException Source #

Socket operation on non-socket.

NOTE: This should be ruled out by the type system.

eDestinationAddressRequired :: SocketException Source #

Destination address required.

eMessageSize :: SocketException Source #

Message too long.

eProtocolType :: SocketException Source #

Protocol wrong type for socket.

eNoProtocolOption :: SocketException Source #

Protocol not available.

eProtocolNotSupported :: SocketException Source #

Protocol not supported.

eSocketTypeNotSupported :: SocketException Source #

Socket type not supported.

eOperationNotSupported :: SocketException Source #

Operation not supported.

eProtocolFamilyNotSupported :: SocketException Source #

Protocol family not supported.

eAddressFamilyNotSupported :: SocketException Source #

Address family not supported by protocol.

eAddressInUse :: SocketException Source #

Address already in use.

eAddressNotAvailable :: SocketException Source #

Cannot assign requested address.

eNetworkUnreachable :: SocketException Source #

Network is unreachable.

eNetworkReset :: SocketException Source #

Network dropped connection on reset.

eConnectionAborted :: SocketException Source #

Software caused connection abort.

eConnectionReset :: SocketException Source #

Connection reset by peer.

eNoBufferSpace :: SocketException Source #

No buffer space available.

eIsConnected :: SocketException Source #

Transport endpoint is already connected.

eNotConnected :: SocketException Source #

Transport endpoint is not connected.

eShutdown :: SocketException Source #

Cannot send after transport endpoint shutdown.

eTooManyReferences :: SocketException Source #

Too many references: cannot splice.

eTimedOut :: SocketException Source #

Connection timed out.

eAlready :: SocketException Source #

Operation already in progress.

NOTE: This exception shall not be thrown by any public operation in this library, but is handled internally.

eInProgress :: SocketException Source #

Operation now in progress

AddressInfoException

newtype AddressInfoException Source #

Contains the error code that can be matched against.

Hint: Use guards or MultiWayIf to match against specific exceptions:

if | e == eaiFail -> ...
   | e == eaiNoName -> ...
   | otherwise -> ...

eaiAgain :: AddressInfoException Source #

AddressInfoException "Temporary failure in name resolution"

eaiBadFlags :: AddressInfoException Source #

AddressInfoException "Bad value for ai_flags"

eaiFail :: AddressInfoException Source #

AddressInfoException "Non-recoverable failure in name resolution"

eaiFamily :: AddressInfoException Source #

AddressInfoException "ai_family not supported"

eaiMemory :: AddressInfoException Source #

AddressInfoException "Memory allocation failure"

eaiNoName :: AddressInfoException Source #

AddressInfoException "No such host is known"

eaiSocketType :: AddressInfoException Source #

AddressInfoException "ai_socktype not supported"

eaiService :: AddressInfoException Source #

AddressInfoException "Servname not supported for ai_socktype"

eaiSystem :: AddressInfoException Source #

AddressInfoException "System error"