Skip to content

Commit

Permalink
Update documentation.
Browse files Browse the repository at this point in the history
  • Loading branch information
Bryan O'Sullivan committed Jan 7, 2009
1 parent c885c2f commit 0d0b990
Show file tree
Hide file tree
Showing 2 changed files with 61 additions and 6 deletions.
2 changes: 1 addition & 1 deletion Network/Socket/ByteString.cpphs
Original file line number Diff line number Diff line change
Expand Up @@ -23,8 +23,8 @@ module Network.Socket.ByteString
(
-- * Send a message on a socket
-- | Functions used to transmit a message to another socket.
send,
sendAll,
send,
sendTo,

-- * Receive a message from a socket
Expand Down
65 changes: 60 additions & 5 deletions Network/Socket/ByteString/Lazy.hsc
Original file line number Diff line number Diff line change
Expand Up @@ -2,13 +2,39 @@

#include <sys/uio.h>

-- |
-- Module : Network.Socket.ByteString.Lazy
-- Copyright : (c) Bryan O'Sullivan 2009
-- License : BSD-style
--
-- Maintainer : [email protected]
-- Stability : experimental
-- Portability : POSIX, GHC
--
-- A module for efficiently transmitting data over sockets. For
-- detailed documentation consult your favorite POSIX socket
-- reference. All functions communicate failures by converting the
-- error number to an 'System.IO.IOError'.
--
-- This module is intended to be imported together with
-- 'Network.Socket' like so:
--
-- > import Network.Socket hiding (send, sendTo, recv, recvFrom)
-- > import Network.Socket.ByteString.Lazy
-- > import Prelude hiding (getContents)
--
-- Alternatively, you can import it qualified.
--
-- > import qualified Network.Socket.ByteString.Lazy as S
module Network.Socket.ByteString.Lazy
(
getContents
-- * Send data on a socket
sendAll
, send
, sendAll
-- * Receive data on a socket
, recv
, recv_
, getContents
) where

import Control.Monad (liftM)
Expand All @@ -23,14 +49,15 @@ import Foreign.Ptr (Ptr, castPtr, plusPtr)
import Foreign.Storable (Storable(..))
import qualified Network.Socket.ByteString as N
import Network.Socket.ByteString.Internal
import Network.Socket (Socket(..))
import Network.Socket (Socket(..), ShutdownCmd(..), shutdown)
import System.IO.Unsafe (unsafeInterleaveIO)
import Prelude hiding (getContents)
import System.Posix.Types (CSsize)
import GHC.Conc (threadWaitRead, threadWaitWrite)

-- | Needed to support the POSIX writev system call.
data IOVec = IOVec { iovBase :: Ptr CChar
, iovLen :: CSize }
, iovLen :: CSize }

instance Storable IOVec where
sizeOf _ = (#const sizeof(struct iovec))
Expand All @@ -45,6 +72,13 @@ instance Storable IOVec where
(#poke struct iovec, iov_base) p (iovBase iov)
(#poke struct iovec, iov_len) p (iovLen iov)

-- | Send a 'ByteString' using a single system call.
--
-- Because a lazily generated 'ByteString' may be arbitrarily long,
-- this function caps the amount it will attempt to send at 4MB. This
-- number is large (so it should not penalize performance on fast
-- networks), but not outrageously so (to avoid demanding lazily
-- computed data unnecessarily early).
send :: Socket -> ByteString -> IO Int64
send (MkSocket fd _ _ _ _) s = do
let cs = L.toChunks s
Expand All @@ -65,31 +99,52 @@ send (MkSocket fd _ _ _ _) s = do
(k + fromIntegral len) (niovs + 1)
| otherwise = f niovs
loop _ _ _ niovs = f niovs
-- Limit the amount of data that we'll try to transmit with a
-- single system call.
sendLimit = 4194304

foreign import ccall unsafe "writev"
c_writev :: CInt -> Ptr IOVec -> CInt -> IO CSsize

-- | Send the entire contents of a string, possibly using multiple
-- 'send' system calls to do so.
sendAll :: Socket -> ByteString -> IO ()
sendAll sock bs = do
sent <- send sock bs
if sent < L.length bs
then sendAll sock (L.drop sent bs)
else return ()

-- | Lazily receive 'ByteString' data, in chunks. Chunks are received
-- on demand; each chunk will be sized to reflect the amount of data
-- received by individual 'recv_' calls.
--
-- All remaining data from the socket data is consumed. The receiving
-- side of the socket is shut down when there is no more data to be
-- received. This does not occur if an exception is thrown.
getContents :: Socket -> IO ByteString
getContents sock@(MkSocket fd _ _ _ _) = loop
where loop = unsafeInterleaveIO $ do
s <- N.recv_ sock defaultChunkSize
if S.null s
then return Empty
then shutdown sock ShutdownReceive >> return Empty

This comment has been minimized.

Copy link
@vdukhovni

vdukhovni Feb 5, 2019

@bos, @eborden, @kazu-yamamoto This shutdown call is causing problems in MacOS tests. Does anyone know why it was added? Adding a shutdown after recv() returns EOF looks redundant.

I can make the MacOS getContents tests pass, by either removing this shutdown, or ignoring some or all IO exceptions that it may raise.

This comment has been minimized.

Copy link
@eborden

eborden Feb 5, 2019

Collaborator

It is generally good practice to send a shutdown back. It isn't completely necessary, but it allows the other end of the socket to know it is safe to close as more data will not be sent. My assumption was that some well placed catch calls would fix this on OSX. I don't have access to a mac, so I'd love if you can contribute a fix.

This comment has been minimized.

Copy link
@vdukhovni

vdukhovni Feb 5, 2019

Firstly, at least with TCP, a SHUT_RD does not send anything to the other end of the socket, TCP can only send FIN, which is a SHUT_WR. Secondly, given that we're getting EOF, there's no need to tell the other side to stop, he's already stopped, so I don't really see the point. Perhaps I'm missing something, but it is not clear what.

I do have access to a Mac, so I'll send a patch, but first it would be good to know why the original shutdown was added. If it was just cosmetic (just in case) then it likely does more harm than good, and should be removed. If there was some problem that adding solved, it would be good to know what that was, and whether it is still relevant.

This comment has been minimized.

Copy link
@vdukhovni

vdukhovni Feb 5, 2019

With the below, the new getContents tests in #375 pass on MacOS without disabling any tests. But I rather suspect that the simpler fix is to just remove the shutdown call, since it is rather unclear why it is needed in the first place.

diff --git a/Network/Socket/ByteString/Lazy.hs b/Network/Socket/ByteString/Lazy.hs
index 735390a..30f137d 100644
--- a/Network/Socket/ByteString/Lazy.hs
+++ b/Network/Socket/ByteString/Lazy.hs
@@ -44,6 +44,7 @@ import qualified Data.ByteString               as S
 import qualified Network.Socket.ByteString     as N
 import           Network.Socket.Imports
 import           Network.Socket.Types
+import qualified System.IO.Error               as E
 
 -- -----------------------------------------------------------------------------
 -- Receiving
@@ -63,9 +64,16 @@ getContents s = loop
   where
     loop = unsafeInterleaveIO $ do
         sbs <- N.recv s defaultChunkSize
-        if S.null sbs
-            then shutdown s ShutdownReceive >> return Empty
-            else Chunk sbs <$> loop
+        if not $ S.null sbs
+            then Chunk sbs <$> loop
+            else do
+                 -- The socket may be closed at the TCP layer by the time we've
+                 -- read EOF, and some systems will return errors when
+                 -- attempting to shut down an closed socket.  In particular,
+                 -- some versions of MacOS return EINVAL.
+                 --
+                 shutdown s ShutdownReceive `E.catchIOError` (\_ -> return ())
+                 return Empty
 
 -- | Receive data from the socket.  The socket must be in a connected
 -- state.  This function may return fewer bytes than specified.  If

This comment has been minimized.

Copy link
@eborden

eborden Feb 5, 2019

Collaborator

Agreed. If removing the shutdown is acceptable then I would prefer that path.

This comment has been minimized.

Copy link
@vdukhovni

vdukhovni Feb 7, 2019

@bos Don't know whether you receive notifications from github. If you do, please comment when you get a chance. I am inclined to recommend removal of the shutdown call at some point if there's no apparent reason to have it.

else Chunk s `liftM` loop

-- | Receive a message. The socket must be in a connected state so
-- that the intended recipient is known. Note that the length of the
-- received data can be smaller than specified maximum length. If the
-- message is longer than the specified length it may be discarded
-- depending on the type of socket. May block until a message arrives.
--
-- When the end of the input stream is reached, returns an empty
-- 'ByteString'.
recv_ :: Socket -> Int64 -> IO ByteString
recv_ sock nbytes = chunk `liftM` N.recv_ sock (fromIntegral nbytes)
where chunk k | S.null k = Empty
| otherwise = Chunk k Empty

-- | Receive a message from another socket. Similar to 'recv_', but
-- throws an EOF exception at end of input.
recv :: Socket -> Int64 -> IO ByteString
recv sock nbytes = chunk `liftM` N.recv sock (fromIntegral nbytes)
where chunk k = Chunk k Empty

1 comment on commit 0d0b990

@kazu-yamamoto
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

We should have bravery to remove unknown code.

Please sign in to comment.