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 | Haskell2010 |
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 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 -- If the prefork technique is not used, -- set CloseOnExec for the security reasons. fd <- fdSocket sock setCloseOnExecIfNeeded fd bind sock (addrAddress addr) 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 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 msg
The 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
- = AI_ADDRCONFIG
- | AI_ALL
- | AI_CANONNAME
- | AI_NUMERICHOST
- | AI_NUMERICSERV
- | AI_PASSIVE
- | AI_V4MAPPED
- 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
- = Debug
- | ReuseAddr
- | Type
- | SoError
- | DontRoute
- | Broadcast
- | SendBuffer
- | RecvBuffer
- | KeepAlive
- | OOBInline
- | TimeToLive
- | MaxSegment
- | NoDelay
- | Cork
- | Linger
- | ReusePort
- | RecvLowWater
- | SendLowWater
- | RecvTimeOut
- | SendTimeOut
- | UseLoopBack
- | UserTimeout
- | IPv6Only
- | CustomSockOpt (CInt, CInt)
- isSupportedSocketOption :: SocketOption -> Bool
- getSocketOption :: Socket -> SocketOption -> IO Int
- setSocketOption :: Socket -> SocketOption -> Int -> IO ()
- data Socket
- socket :: Family -> SocketType -> ProtocolNumber -> IO Socket
- fdSocket :: Socket -> IO CInt
- mkSocket :: CInt -> 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
- 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
- = NI_DGRAM
- | NI_NAMEREQD
- | NI_NOFQDN
- | NI_NUMERICHOST
- | NI_NUMERICSERV
- 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
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
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 addr
127.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
Fields
Instances
Instance details
Defined in Network.Socket.Info
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 defaultHints
AF_UNSPEC>>>
addrSocketType defaultHints
NoSocketType>>>
addrProtocol defaultHints
0
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
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.
(Only some platforms support this.)
If AI_ALL
is specified, return all matching IPv6 and
IPv4 addresses. Otherwise, this flag has no effect.
(Only some platforms support this.)
The addrCanonName
field of the first returned
AddrInfo
will contain the "canonical name" of the host.
The HostName
argument must be a numeric
address in string form, and network name lookups will not be
attempted.
The ServiceName
argument must be a port
number in string form, and service name lookups will not be
attempted. (Only some platforms support this.)
If no HostName
value is provided, the network
address in each SockAddr
will be left as a "wild card".
This is useful for server applications that
will accept connections from any client.
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
Instance details
Defined in Network.Socket.Info
Methods
(==) :: AddrInfoFlag -> AddrInfoFlag -> Bool #
(/=) :: AddrInfoFlag -> AddrInfoFlag -> Bool #
Instance details
Defined in Network.Socket.Info
Methods
readsPrec :: Int -> ReadS AddrInfoFlag #
readList :: ReadS [AddrInfoFlag] #
Instance details
Defined in Network.Socket.Info
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.
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.
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 #
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
SO_DEBUG
SO_REUSEADDR
SO_TYPE
SO_ERROR
SO_DONTROUTE
SO_BROADCAST
SO_SNDBUF
SO_RCVBUF
SO_KEEPALIVE
SO_OOBINLINE
IP_TTL
TCP_MAXSEG
TCP_NODELAY
TCP_CORK
SO_LINGER: timeout in seconds, 0 means disabling/disabled.
SO_REUSEPORT
SO_RCVLOWAT
SO_SNDLOWAT
SO_RCVTIMEO: this does not work at this moment.
SO_SNDTIMEO: this does not work at this moment.
SO_USELOOPBACK
TCP_USER_TIMEOUT
IPV6_V6ONLY: don't use this on OpenBSD.
Instances
Instance details
Defined in Network.Socket.Options
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
Basic type for a socket.
Instances
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 sock
127.0.0.1:5000
fdSocket :: Socket -> IO CInt Source #
Getting a 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
.
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
0, used in getAddrInfo hints, for example
SOCK_STREAM
SOCK_DGRAM
SOCK_RAW
SOCK_RDM
SOCK_SEQPACKET
Instances
Instance details
Defined in Network.Socket.Types
Instance details
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 #
Instance details
Defined in Network.Socket.Types
Methods
readsPrec :: Int -> ReadS SocketType #
readList :: ReadS [SocketType] #
readPrec :: ReadPrec SocketType #
readListPrec :: ReadPrec [SocketType] #
Instance details
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
unspecified
UNIX-domain
Internet Protocol version 4
Internet Protocol version 6
Arpanet imp addresses
pup protocols: e.g. BSP
mit CHAOS protocols
XEROX NS protocols
nbs protocols
european computer manufacturers
datakit protocols
CCITT protocols, X.25 etc
IBM SNA
DECnet
Direct data link interface
LAT
NSC Hyperchannel
Apple Talk
Internal Routing Protocol (aka AF_NETLINK)
NetBios-style addresses
Network Interface Tap
IEEE 802.2, also ISO 8802
ISO protocols
umbrella of all families used by OSI
DNA Network Management
CCITT X.25
AX25
AFI
US Government OSI
Novell Internet Protocol
eXpress Transfer Protocol (no AF)
Common Trace Facility
Wide Area Network protocols
SGI Data Link for DLPI
Netware
NDD
Debugging use only
connection-oriented IP, aka ST II
Computer Network Technology
Help Identify RTIP packets
Help Identify PIP packets
Simple Internet Protocol
Integrated Services Digital Network
Internal key-management function
native ATM access
ARP (RFC 826)
Used by BPF to not rewrite hdrs in iface output
ENCAP
Link layer interface
Link layer interface
raw interface
Amateur radio NetROM
multiprotocol bridge
ATM PVCs
Amateur Radio X.25 PLP
Netbeui 802.2LLC
Security callback pseudo AF
Packet family
Ash
Acorn Econet
ATM SVCs
IRDA sockets
PPPoX sockets
Wanpipe API sockets
bluetooth sockets
Controller Area Network
isSupportedFamily :: Family -> Bool Source #
Does the AF_ constant corresponding to the given family exist on this system?
Protocol number
type ProtocolNumber = CInt Source #
Protocl number.
defaultProtocol :: ProtocolNumber Source #
This is the default protocol for a given service.
>>>
defaultProtocol
0
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
Instances
Instance details
Defined in Network.Socket.Types
Instance details
Defined in Network.Socket.Types
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 :: PortNumber
1>>>
read "1" :: PortNumber
1>>>
show (12345 :: PortNumber)
"12345">>>
50000 < (51000 :: PortNumber)
True>>>
50000 < (52000 :: PortNumber)
True>>>
50000 + (10000 :: PortNumber)
60000
Instances
Instance details
Defined in Network.Socket.Types
Methods
succ :: PortNumber -> PortNumber #
pred :: PortNumber -> PortNumber #
toEnum :: Int -> PortNumber #
fromEnum :: PortNumber -> Int #
enumFrom :: PortNumber -> [PortNumber] #
enumFromThen :: PortNumber -> PortNumber -> [PortNumber] #
enumFromTo :: PortNumber -> PortNumber -> [PortNumber] #
enumFromThenTo :: PortNumber -> PortNumber -> PortNumber -> [PortNumber] #
Instance details
Defined in Network.Socket.Types
Instance details
Defined in Network.Socket.Types
Methods
quot :: PortNumber -> PortNumber -> PortNumber #
rem :: PortNumber -> PortNumber -> PortNumber #
div :: PortNumber -> PortNumber -> PortNumber #
mod :: PortNumber -> PortNumber -> PortNumber #
quotRem :: PortNumber -> PortNumber -> (PortNumber, PortNumber) #
divMod :: PortNumber -> PortNumber -> (PortNumber, PortNumber) #
toInteger :: PortNumber -> Integer #
Instance details
Defined in Network.Socket.Types
Methods
(+) :: PortNumber -> PortNumber -> PortNumber #
(-) :: PortNumber -> PortNumber -> PortNumber #
(*) :: PortNumber -> PortNumber -> PortNumber #
negate :: PortNumber -> PortNumber #
abs :: PortNumber -> PortNumber #
signum :: PortNumber -> PortNumber #
fromInteger :: Integer -> PortNumber #
Instance details
Defined in Network.Socket.Types
Methods
compare :: PortNumber -> PortNumber -> Ordering #
(<) :: PortNumber -> PortNumber -> Bool #
(<=) :: PortNumber -> PortNumber -> Bool #
(>) :: PortNumber -> PortNumber -> Bool #
(>=) :: PortNumber -> PortNumber -> Bool #
max :: PortNumber -> PortNumber -> PortNumber #
min :: PortNumber -> PortNumber -> PortNumber #
Instance details
Defined in Network.Socket.Types
Methods
readsPrec :: Int -> ReadS PortNumber #
readList :: ReadS [PortNumber] #
readPrec :: ReadPrec PortNumber #
readListPrec :: ReadPrec [PortNumber] #
Instance details
Defined in Network.Socket.Types
Methods
showsPrec :: Int -> PortNumber -> ShowS #
show :: PortNumber -> String #
showList :: [PortNumber] -> ShowS #
Instance details
Defined in Network.Socket.Types
Methods
sizeOf :: PortNumber -> Int #
alignment :: PortNumber -> Int #
peekElemOff :: Ptr PortNumber -> Int -> IO PortNumber #
pokeElemOff :: Ptr PortNumber -> Int -> PortNumber -> IO () #
peekByteOff :: Ptr b -> Int -> IO PortNumber #
pokeByteOff :: Ptr b -> Int -> PortNumber -> IO () #
peek :: Ptr PortNumber -> IO PortNumber #
poke :: Ptr PortNumber -> PortNumber -> IO () #
defaultPort :: PortNumber Source #
Default port number.
>>>
defaultPort
0
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 2.7.0.0.
socketPair :: Family -> SocketType -> ProtocolNumber -> IO (Socket, Socket) Source #
Build a pair of connected socket objects.
For portability, use this function in the case
where isUnixDomainSocketAvailable
is True
and specify AF_UNIX
to the first argument.
sendFd :: Socket -> CInt -> IO () Source #
Send a file descriptor over a UNIX-domain socket.
Use this function in the case where isUnixDomainSocketAvailable
is
True
.
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
.
Use this function in the case where isUnixDomainSocketAvailable
is
True
.
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
flags to control lookup behaviour
whether to look up a hostname
whether to look up a service name
the address to look up
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
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.
If the hostname cannot be looked up, an IO error is thrown.
If a host is local, return only the hostname part of the FQDN.
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.
The name of the service is not looked up. Instead, a numeric representation of the service is returned.
Instances
Instance details
Defined in Network.Socket.Info
Methods
(==) :: NameInfoFlag -> NameInfoFlag -> Bool #
(/=) :: NameInfoFlag -> NameInfoFlag -> Bool #
Instance details
Defined in Network.Socket.Info
Methods
readsPrec :: Int -> ReadS NameInfoFlag #
readList :: ReadS [NameInfoFlag] #
Instance details
Defined in Network.Socket.Info
Methods
showsPrec :: Int -> NameInfoFlag -> ShowS #
show :: NameInfoFlag -> String #
showList :: [NameInfoFlag] -> ShowS #
Low level
socket operations
setCloseOnExecIfNeeded :: CInt -> IO () Source #
Set the nonblocking 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 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.
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.
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.
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)
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.