| Copyright | (c) Lars Petersen 2015 |
|---|---|
| License | MIT |
| Maintainer | info@lars-petersen.net |
| Stability | experimental |
| Safe Haskell | None |
| Language | Haskell2010 |
System.Socket
Description
This starts a TCP server on localhost, sends "Hello world!" to
connecting peers and closes the connection immediately.
{-# LANGUAGE OverloadedStrings #-}
module Main where
import System.Socket
import System.Socket.Family.INET (inaddrLOOPBACK)
import Data.Monoid
import Data.ByteString
import Control.Monad
import Control.Concurrent
import Control.Exception
main :: IO ()
main = do
s <- socket :: IO (Socket INET STREAM TCP)
setSockOpt s (SO_REUSEADDR True)
bind s (SockAddrIn 8080 inaddrLOOPBACK)
listen s 5
forever $ do
(peer,addr) <- accept s
forkIO $ do
sendAll peer "Hello world!" mempty `finally` close peerThis downloads the [Haskell website](http://www.haskell.org) and shows how to handle exceptions. Note the use of IPv4-mapped IPv6 addresses: This will work even if you don't have IPv6 connectivity yet and is the preferred method when writing new applications.
{-# LANGUAGE OverloadedStrings #-}
module Main where
import Control.Monad
import Control.Exception
import Data.Function (fix)
import qualified Data.ByteString as BS
import System.IO
import System.Exit
import System.Socket
main :: IO ()
main = fetch
`catch` (\e-> do
hPutStr stderr "Something failed when resolving the name: "
hPutStrLn stderr $ show (e :: AddrInfoException)
exitFailure
)
`catch` (\e-> do
hPutStr stderr "Something went wrong with the socket: "
hPutStrLn stderr $ show (e :: SocketException)
exitFailure
)
fetch :: IO ()
fetch = do
addrs <- getAddrInfo6 (Just "www.haskell.org") (Just "80") aiV4MAPPED :: IO [AddrInfo INET6 STREAM TCP]
case addrs of
(addr:_) ->
-- always use the `bracket` pattern to reliably release resources!
bracket
( socket :: IO (Socket INET6 STREAM TCP) )
( close )
( \s-> do connect s (addrAddress addr)
sendAll s "GET / HTTP/1.0\r\nHost: www.haskell.org\r\n\r\n" mempty
fix $ \recvMore-> do
bs <- recv s 4096 mempty
BS.putStr bs
if BS.length bs == 0 -- an empty string means the peer terminated the connection
then exitSuccess
else recvMore
)
_ -> error "Illegal state: getAddrInfo yields non-empty list or exception."- data AddrInfo f t p = AddrInfo {}
- class Family f => GetAddrInfo f where
- getAddrInfo :: (Type t, Protocol p) => Maybe ByteString -> Maybe ByteString -> AddrInfoFlags -> IO [AddrInfo f t p]
- class Family f => GetNameInfo f where
- getNameInfo :: SockAddr f -> NameInfoFlags -> IO (ByteString, ByteString)
- socket :: (Family f, Type t, Protocol p) => IO (Socket f t p)
- connect :: Family f => Socket f t p -> SockAddr f -> IO ()
- bind :: Family f => Socket f t p -> SockAddr f -> IO ()
- listen :: Socket f t p -> Int -> IO ()
- accept :: Family f => Socket f t p -> IO (Socket f t p, SockAddr f)
- send :: Socket f t p -> ByteString -> MsgFlags -> IO Int
- sendTo :: Family f => Socket f t p -> ByteString -> MsgFlags -> SockAddr f -> IO Int
- recv :: Socket f t p -> Int -> MsgFlags -> IO ByteString
- recvFrom :: Family f => Socket f t p -> Int -> MsgFlags -> IO (ByteString, SockAddr f)
- close :: Socket f t p -> IO ()
- sendAll :: Socket f STREAM p -> ByteString -> MsgFlags -> IO ()
- newtype Socket f t p = Socket (MVar Fd)
- class Storable (SockAddr f) => Family f where
- type SockAddr f
- familyNumber :: f -> CInt
- data INET
- data SockAddrIn = SockAddrIn {}
- data INET6
- data SockAddrIn6 = SockAddrIn6 {
- sin6Port :: Word16
- sin6Flowinfo :: Word32
- sin6Addr :: AddrIn6
- sin6ScopeId :: Word32
- class Type t where
- typeNumber :: t -> CInt
- data DGRAM
- data RAW
- data SEQPACKET
- data STREAM
- class Protocol p where
- protocolNumber :: p -> CInt
- data UDP
- data TCP
- newtype SocketException = SocketException CInt
- eOK :: SocketException
- eINTR :: SocketException
- eAGAIN :: SocketException
- eWOULDBLOCK :: SocketException
- eBADF :: SocketException
- eINPROGRESS :: SocketException
- ePROTONOSUPPORT :: SocketException
- eINVAL :: SocketException
- eCONNREFUSED :: SocketException
- newtype AddrInfoException = AddrInfoException CInt
- gaiStrerror :: AddrInfoException -> String
- eaiAGAIN :: AddrInfoException
- eaiBADFLAGS :: AddrInfoException
- eaiFAIL :: AddrInfoException
- eaiFAMILY :: AddrInfoException
- eaiMEMORY :: AddrInfoException
- eaiNONAME :: AddrInfoException
- eaiSOCKTYPE :: AddrInfoException
- eaiSERVICE :: AddrInfoException
- eaiSYSTEM :: AddrInfoException
- class GetSockOpt o where
- getSockOpt :: Socket f t p -> IO o
- class SetSockOpt o where
- setSockOpt :: Socket f t p -> o -> IO ()
- data SO_ACCEPTCONN = SO_ACCEPTCONN Bool
- data SO_REUSEADDR = SO_REUSEADDR Bool
- newtype MsgFlags = MsgFlags CInt
- msgDONTWAIT :: MsgFlags
- msgEOR :: MsgFlags
- msgMORE :: MsgFlags
- msgNOSIGNAL :: MsgFlags
- msgOOB :: MsgFlags
- msgTRUNC :: MsgFlags
- msgWAITALL :: MsgFlags
- newtype AddrInfoFlags = AddrInfoFlags CInt
- aiADDRCONFIG :: AddrInfoFlags
- aiALL :: AddrInfoFlags
- aiCANONNAME :: AddrInfoFlags
- aiNUMERICHOST :: AddrInfoFlags
- aiNUMERICSERV :: AddrInfoFlags
- aiPASSIVE :: AddrInfoFlags
- aiV4MAPPED :: AddrInfoFlags
- newtype NameInfoFlags = NameInfoFlags CInt
- niNAMEREQD :: NameInfoFlags
- niDGRAM :: NameInfoFlags
- niNOFQDN :: NameInfoFlags
- niNUMERICHOST :: NameInfoFlags
- niNUMERICSERV :: NameInfoFlags
Name Resolution
Constructors
| AddrInfo | |
Fields | |
getAddrInfo
class Family f => GetAddrInfo f where Source
Methods
getAddrInfo :: (Type t, Protocol p) => Maybe ByteString -> Maybe ByteString -> AddrInfoFlags -> IO [AddrInfo f t p] Source
Maps names to addresses (i.e. by DNS lookup).
The operation throws AddrInfoExceptions.
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.
> getAddrInfo (Just "www.haskell.org") (Just "80") aiV4MAPPED :: IO [AddrInfo INET6 STREAM TCP]
[AddrInfo {addrInfoFlags = AddrInfoFlags 8, addrAddress = [2400:cb00:2048:0001:0000:0000:6ca2:cc3c]:80, addrCanonName = Nothing}]
> getAddrInfo (Just "darcs.haskell.org") Nothing aiV4MAPPED :: IO [AddrInfo INET6 STREAM TCP]
[AddrInfo {addrInfoFlags = AddrInfoFlags 8, addrAddress = [0000:0000:0000:0000:0000:ffff:17fd:e1ad]:0, addrCanonName = Nothing}]
> getAddrInfo (Just "darcs.haskell.org") Nothing mempty :: IO [AddrInfo INET6 STREAM TCP]
*** Exception: AddrInfoException "Name or service not known"Instances
getNameInfo
class Family f => GetNameInfo f where Source
Maps addresss to readable host- and service names.
The operation throws AddrInfoExceptions.
> getNameInfo (SockAddrIn 80 inaddrLOOPBACK) mempty
("localhost.localdomain","http")Methods
getNameInfo :: SockAddr f -> NameInfoFlags -> IO (ByteString, ByteString) Source
Instances
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 DGRAM 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
closethe socket when it's no longer needed. If possible, usebracketto 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 yourmanpage for details and specificerrnos.
connect
connect :: Family f => Socket f t p -> SockAddr f -> IO () Source
Connects to an remote address.
- Calling
connecton aclosed socket throwsEBADFeven if the former file descriptor has been reassigned. - This function returns as soon as a connection has either been established
or refused. A failed connection attempt does not throw an exception
if
EINTRorEINPROGRESSwere caught internally. The operation just unblocks and returns in this case. The approach is to just try to read or write the socket and eventually fail there instead. Also see [these considerations](http:/cr.yp.todocs/connect.html) for an explanation. - This operation throws
SocketExceptions. Consult yourmanpage for details and specificerrnos. EINTRandEINPROGRESSget catched internally and won't be thrown as the connection might still be established asynchronously. Expect failure when trying to read or write the socket in this case.
bind
bind :: Family f => Socket f t p -> SockAddr f -> IO () Source
Bind a socket to an address.
- Calling
bindon aclosed socket throwsEBADFeven if the former file descriptor has been reassigned. - It is assumed that
c_bindnever blocks and thereforeEINPROGRESS,EALREADYandEINTRdon'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](http:/stackoverflow.coma/14485305). - This operation throws
SocketExceptions. Consult yourmanpage for details and specificerrnos.
listen
listen :: Socket f t p -> Int -> IO () Source
Starts listening and queueing connection requests on a connection-mode socket.
- Calling
listenon aclosed socket throwsEBADFeven 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
0leaves the decision to the implementation. - This operation throws
SocketExceptions. Consult yourmanpage for details and specificerrnos.
accept
accept :: Family f => Socket f t p -> IO (Socket f t p, SockAddr f) Source
Accept a new connection.
- Calling
accepton aclosed socket throwsEBADFeven if the former file descriptor has been reassigned. - This operation configures the new socket non-blocking (TODO: use
accept4if 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
closethe socket when it's no longer needed. - This operation throws
SocketExceptions. Consult yourmanpage for details and specificerrnos. - This operation catches
EAGAIN,EWOULDBLOCKandEINTRinternally and retries automatically.
send, sendTo
send :: Socket f t p -> ByteString -> MsgFlags -> IO Int Source
Send a message on a connected socket.
- Calling
sendon aclosed socket throwsEBADFeven if the former file descriptor has been reassigned. - The operation returns the number of bytes sent. On
DGRAMandSEQPACKETsockets certain assurances on atomicity exist andEAGAINorEWOULDBLOCKare returned until the whole message would fit into the send buffer. - The flag
MSG_NOSIGNALis set to supress signals which are pointless. - This operation throws
SocketExceptions. Consultman 3p sendfor details and specificerrnos. EAGAIN,EWOULDBLOCKandEINTRand handled internally and won't be thrown. For performance reasons the operation first tries a write on the socket and then waits when it gotEAGAINorEWOULDBLOCK.
sendTo :: Family f => Socket f t p -> ByteString -> MsgFlags -> SockAddr f -> IO Int Source
Like send, but allows for specifying a destination address.
recv, recvFrom
recv :: Socket f t p -> Int -> MsgFlags -> IO ByteString Source
Receive a message on a connected socket.
- Calling
recvon aclosed socket throwsEBADFeven 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
SocketExceptions. Consultman 3p recvfor details and specificerrnos. EAGAIN,EWOULDBLOCKandEINTRand handled internally and won't be thrown. For performance reasons the operation first tries a read on the socket and then waits when it gotEAGAINorEWOULDBLOCK.
recvFrom :: Family f => Socket f t p -> Int -> MsgFlags -> IO (ByteString, SockAddr f) Source
Like recv, 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
closeon this socket will fail withEBADFafter the socket has been closed (closereplaces theFdin theMVarwith-1to reliably avoid use-after-free situations). - This operation potentially throws
SocketExceptions (onlyEIOis documented).EINTRis catched internally and retried automatically, so won't be thrown.
Convenience Operations
sendAll
sendAll :: Socket f STREAM p -> ByteString -> MsgFlags -> IO () Source
Like send, but continues until all data has been sent.
sendAll sock buf flags = do sent <- send sock buf flags when (sent < length buf) $ sendAll sock (drop sent buf) flags
Sockets
A generic socket type. Also see socket for details.
The socket is just an MVar-wrapped file descriptor.
It is exposed 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
withMVaror 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
threadWaitReadas it does not seperate 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](https:/mail.haskell.orgpipermailhaskell-cafe2014-September/115823.html) thread and read the library code to see how the problem is currently circumvented.
Families
INET
Instances
INET6
Instances
data SockAddrIn6 Source
Constructors
| SockAddrIn6 | |
Fields
| |
Instances
Types
Methods
typeNumber :: t -> CInt Source
DGRAM
RAW
SEQPACKET
STREAM
Protocols
Methods
protocolNumber :: p -> CInt Source
UDP
TCP
Exceptions
SocketException
newtype SocketException Source
Constructors
| SocketException CInt |
AddrInfoException
newtype AddrInfoException Source
Contains the error code that can be matched against. Use gaiStrerror
to get a human readable explanation of the error (show`
does this as well).
Constructors
| AddrInfoException CInt |
gaiStrerror :: AddrInfoException -> String Source
A wrapper around gai_strerror.
eaiAGAIN :: AddrInfoException Source
AddrInfoException "Temporary failure in name resolution"
eaiBADFLAGS :: AddrInfoException Source
AddrInfoException "Bad value for ai_flags"
eaiFAIL :: AddrInfoException Source
AddrInfoException "Non-recoverable failure in name resolution"
eaiFAMILY :: AddrInfoException Source
AddrInfoException "ai_family not supported"
eaiMEMORY :: AddrInfoException Source
AddrInfoException "Memory allocation failure"
eaiNONAME :: AddrInfoException Source
AddrInfoException "No such host is known"
eaiSOCKTYPE :: AddrInfoException Source
AddrInfoException "ai_socktype not supported"
eaiSERVICE :: AddrInfoException Source
AddrInfoException "Servname not supported for ai_socktype"
eaiSYSTEM :: AddrInfoException Source
AddrInfoException "System error"
Options
SO_ACCEPTCONN
SO_REUSEADDR
Flags
MsgFlags
AddrInfoFlags
newtype AddrInfoFlags Source
Use the Monoid instance to combine several flags:
mconcat [aiADDRCONFIG, aiV4MAPPED]
Constructors
| AddrInfoFlags CInt |
NameInfoFlags
newtype NameInfoFlags Source
Use the Monoid instance to combine several flags:
mconcat [niNAMEREQD, niNOFQDN]
Constructors
| NameInfoFlags CInt |
niNAMEREQD :: NameInfoFlags Source
Throw an exception if the hostname cannot be determined.
niDGRAM :: NameInfoFlags Source
Service is datagram based (UDP) rather than stream based (TCP).
niNOFQDN :: NameInfoFlags Source
Return only the hostname part of the fully qualified domain name for local hosts.
niNUMERICHOST :: NameInfoFlags Source
Return the numeric form of the host address.
niNUMERICSERV :: NameInfoFlags Source
Return the numeric form of the service address.