Copyright | (c) Lars Petersen 2015 |
---|---|
License | MIT |
Maintainer | info@lars-petersen.net |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
{-# 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 )
- data Socket f t p
- data family SocketAddress f
- class Family f where
- class Type t where
- class Protocol p where
- socket :: (Family f, Type t, Protocol p) => IO (Socket f t p)
- connect :: (Family f, Storable (SocketAddress f)) => Socket f t p -> SocketAddress f -> IO ()
- bind :: (Family f, Storable (SocketAddress f)) => Socket f t p -> SocketAddress f -> IO ()
- listen :: Socket f t p -> Int -> IO ()
- accept :: (Family f, Storable (SocketAddress f)) => Socket f t p -> IO (Socket f t p, SocketAddress f)
- send :: Socket f t p -> ByteString -> MessageFlags -> IO Int
- sendTo :: (Family f, Storable (SocketAddress f)) => Socket f t p -> ByteString -> MessageFlags -> SocketAddress f -> IO Int
- receive :: Socket f t p -> Int -> MessageFlags -> IO ByteString
- receiveFrom :: (Family f, Storable (SocketAddress f)) => Socket f t p -> Int -> MessageFlags -> IO (ByteString, SocketAddress f)
- close :: Socket f t p -> IO ()
- class SocketOption o where
- data Error = Error SocketException
- data ReuseAddress = ReuseAddress Bool
- data AddressInfo f t p = AddressInfo {}
- class Family f => HasAddressInfo f where
- data NameInfo = NameInfo {}
- class Family f => HasNameInfo f where
- newtype MessageFlags = MessageFlags CInt
- msgEndOfRecord :: MessageFlags
- msgNoSignal :: MessageFlags
- msgOutOfBand :: MessageFlags
- msgWaitAll :: MessageFlags
- data AddressInfoFlags
- aiAddressConfig :: AddressInfoFlags
- aiAll :: AddressInfoFlags
- aiCanonicalName :: AddressInfoFlags
- aiNumericHost :: AddressInfoFlags
- aiNumericService :: AddressInfoFlags
- aiPassive :: AddressInfoFlags
- aiV4Mapped :: AddressInfoFlags
- data NameInfoFlags
- niNameRequired :: NameInfoFlags
- niDatagram :: NameInfoFlags
- niNoFullyQualifiedDomainName :: NameInfoFlags
- niNumericHost :: NameInfoFlags
- niNumericService :: NameInfoFlags
- newtype SocketException = SocketException CInt
- eOk :: SocketException
- eInterrupted :: SocketException
- eBadFileDescriptor :: SocketException
- eInvalid :: SocketException
- ePipe :: SocketException
- eWouldBlock :: SocketException
- eAgain :: SocketException
- eNotSocket :: SocketException
- eDestinationAddressRequired :: SocketException
- eMessageSize :: SocketException
- eProtocolType :: SocketException
- eNoProtocolOption :: SocketException
- eProtocolNotSupported :: SocketException
- eSocketTypeNotSupported :: SocketException
- eOperationNotSupported :: SocketException
- eProtocolFamilyNotSupported :: SocketException
- eAddressFamilyNotSupported :: SocketException
- eAddressInUse :: SocketException
- eAddressNotAvailable :: SocketException
- eNetworkDown :: SocketException
- eNetworkUnreachable :: SocketException
- eNetworkReset :: SocketException
- eConnectionAborted :: SocketException
- eConnectionReset :: SocketException
- eNoBufferSpace :: SocketException
- eIsConnected :: SocketException
- eNotConnected :: SocketException
- eShutdown :: SocketException
- eTooManyReferences :: SocketException
- eTimedOut :: SocketException
- eConnectionRefused :: SocketException
- eHostDown :: SocketException
- eHostUnreachable :: SocketException
- eAlready :: SocketException
- eInProgress :: SocketException
- newtype AddressInfoException = AddressInfoException CInt
- eaiAgain :: AddressInfoException
- eaiBadFlags :: AddressInfoException
- eaiFail :: AddressInfoException
- eaiFamily :: AddressInfoException
- eaiMemory :: AddressInfoException
- eaiNoName :: AddressInfoException
- eaiSocketType :: AddressInfoException
- eaiService :: AddressInfoException
- eaiSystem :: AddressInfoException
Socket
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 totally different connection. 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.
data family SocketAddress f Source #
The SocketAddress
type is a data family.
This allows to provide different data constructors depending on the socket
family wihtout knowing all of them in advance or the need to patch this
core library.
SocketAddressInet inetLoopback 8080 :: SocketAddress Inet SocketAddressInet6 inet6Loopback 8080 0 0 :: SocketAddress Inet6
Eq (SocketAddress Inet6) # | |
Eq (SocketAddress Inet) # | |
Show (SocketAddress Inet6) # | |
Show (SocketAddress Inet) # | |
Storable (SocketAddress Inet6) # | |
Storable (SocketAddress Inet) # | |
data SocketAddress Inet6 Source # | An IPv6 socket address. The socket address contains a port number that may be used by transport protocols like TCP. SocketAddressInet6 inet6Loopback 8080 0 0 |
data SocketAddress Inet Source # | An IPv4 socket address. The socket address contains a port number that may be used by transport protocols like TCP. SocketAddressInet inetLoopback 8080 |
Family
familyNumber :: f -> CInt Source #
Type
typeNumber :: t -> CInt Source #
Protocol
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 escpecially simplifies the handling of addresses (by using associated type families). Examples:
-- create a IPv4-UDP-datagram socket sock <- socket :: IO (Socket Inet Datagram UDP) -- create a IPv6-TCP-streaming socket sock6 <- socket :: IO (Socket Inet6 Stream TCP)
- 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, usebracket
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
SocketException
s. Consult yourman
page for details and specificerrno
s.
connect
connect :: (Family f, Storable (SocketAddress 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 socket is locked throughout the whole operation.
- The operation throws
SocketException
s. Callingconnect
on aclose
d socket throwseBadFileDescriptor
even if the former file descriptor has been reassigned.
bind
bind :: (Family f, Storable (SocketAddress f)) => Socket f t p -> SocketAddress f -> IO () Source #
Bind a socket to an address.
- Calling
bind
on aclose
d socket throwseBadFileDescriptor
even if the former file descriptor has been reassigned. - It is assumed that
bind
never blocks and thereforeeInProgress
,eAlready
andeInterrupted
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
SocketException
s. Consult yourman
page for details and specificerrno
s.
listen
listen :: Socket f t p -> Int -> IO () Source #
Starts listening and queueing connection requests on a connection-mode socket.
- Calling
listen
on aclose
d socket throwseBadFileDescriptor
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 socket implementation shall queue. A value
of
0
leaves the decision to the implementation. - This operation throws
SocketException
s. Consult yourman
page for details and specificerrno
s.
accept
accept :: (Family f, Storable (SocketAddress f)) => Socket f t p -> IO (Socket f t p, SocketAddress f) Source #
Accept a new connection.
- Calling
accept
on aclose
d socket throwseBadFileDescriptor
even if the former file descriptor has been reassigned. - This operation configures the new socket non-blocking (TODO: use
accept4
if available). - 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
SocketException
s. Consult yourman
page for details and specificerrno
s. - This operation catches
eAgain
,eWouldBlock
andeInterrupted
internally and retries automatically.
send, sendTo
send :: Socket f t p -> ByteString -> MessageFlags -> IO Int Source #
Send a message on a connected socket.
- Calling
send
on aclose
d socket throwseBadFileDescriptor
even if the former file descriptor has been reassigned. - The operation returns the number of bytes sent. On
Datagram
andSequentialPacket
sockets certain assurances on atomicity exist andeAgain
oreWouldBlock
are returned until the whole message would fit into the send buffer. - This operation throws
SocketException
s. Consultman 3p send
for details and specificerrno
s. eAgain
,eWouldBlock
andeInterrupted
and handled internally and won't be thrown. For performance reasons the operation first tries a write on the socket and then waits when it goteAgain
oreWouldBlock
.
sendTo :: (Family f, Storable (SocketAddress 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 a message on a connected socket.
- Calling
receive
on aclose
d socket throwseBadFileDescriptor
even if the former file descriptor has been reassigned. - The operation takes a buffer size in bytes a first parameter which
limits the maximum length of the returned
ByteString
. - This operation throws
SocketException
s. Consultman 3p receive
for details and specificerrno
s. eAgain
,eWouldBlock
andeInterrupted
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 goteAgain
oreWouldBlock
.
receiveFrom :: (Family f, Storable (SocketAddress 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 not to block on operations on this socket in the future.
Threads that perform operations other than
close
on this socket will fail witheBadFileDescriptor
after the socket has been closed (close
replaces theFd
in theMVar
with-1
to reliably avoid use-after-free situations). - This operation potentially throws
SocketException
s (onlyEIO
is documented).eInterrupted
is catched internally and retried automatically, so won't be thrown.
Options
class SocketOption o where Source #
getSocketOption :: Socket f t p -> IO o Source #
setSocketOption :: Socket f t p -> o -> IO () Source #
SO_ERROR
data ReuseAddress Source #
SO_REUSEADDR
Name Resolution
getAddressInfo
data AddressInfo f t p Source #
Eq (SocketAddress f) => Eq (AddressInfo f t p) Source # | |
Show (SocketAddress f) => Show (AddressInfo f t p) Source # | |
class Family f => HasAddressInfo f where Source #
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 AddressInfoException
s.
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
A NameInfo
consists of host and service name.
class Family f => HasNameInfo f where Source #
Maps addresses to readable host- and service names.
The operation throws AddressInfoException
s.
> getNameInfo (SocketAddressInet inetLoopback 80) mempty NameInfo {hostName = "localhost.localdomain", serviceName = "http"}
getNameInfo :: SocketAddress f -> NameInfoFlags -> IO NameInfo Source #
Flags
MessageFlags
newtype MessageFlags Source #
msgEndOfRecord :: MessageFlags Source #
MSG_EOR
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 optionSO_NOSIGPIPE
may be used disable signals on a per-socket basis.
msgOutOfBand :: MessageFlags Source #
MSG_OOB
msgWaitAll :: MessageFlags Source #
MSG_WAITALL
AddressInfoFlags
data AddressInfoFlags Source #
Use the Monoid
instance to combine several flags:
mconcat [aiAddressConfig, aiV4Mapped]
aiAddressConfig :: AddressInfoFlags Source #
AI_ADDRCONFIG
:
aiAll :: AddressInfoFlags Source #
AI_ALL
: Return both IPv4 (as mapped SocketAddressInet6
) and IPv6 addresses when
aiV4Mapped
is set independent of whether IPv6 addresses exist for this
name.
aiCanonicalName :: AddressInfoFlags Source #
AI_CANONNAME
:
aiNumericHost :: AddressInfoFlags Source #
AI_NUMERICHOST
:
aiNumericService :: AddressInfoFlags Source #
AI_NUMERICSERV
:
aiPassive :: AddressInfoFlags Source #
AI_PASSIVE
:
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]
niNameRequired :: NameInfoFlags Source #
NI_NAMEREQD
: Throw an exception if the hostname cannot be determined.
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 #
AddressInfoException
newtype AddressInfoException Source #
Contains the error code that can be matched against. Use show
to get a human readable explanation of the error.
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"