Hi Ruben,<br><br>This signal is used internally by Haskell IO manager, nothing is wrong with it.<br><br>What I see in the dump is that 198.255.92.74 is announcing window of size 0 from the beginning and tapioca ends up sending 0 window too. Are you sure they both reading what other one sends to them? Given that your code only fails on large files, I guess sender never reads this 4-byte status messages receiver sends to it, and processes deadlock after socket buffer is filled up.<br><br>As a side node, consider using putWord32be from binary or cereal packages instead of serializing data yourself.<br><div class="gmail_quote"><div dir="ltr">On Tue, 12 Jul 2016 at 03:35, Ruben Astudillo <<a href="mailto:ruben.astud@gmail.com">ruben.astud@gmail.com</a>> wrote:<br></div><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">Hi all<br>
<br>
I am doing a DCC subsystem on a irc client. After all the handshakes are<br>
done I just connect to the server and start `recv`. The code I use for<br>
this is:<br>
<br>
     getPackets :: MVar Int<br>
                -> FilePath -- ^ Name media<br>
                -> Int      -- ^ File size<br>
                -> AddrInfo -> ExceptT DCCError IO ()<br>
     getPackets mvar name totalSize addr =<br>
       do receivedSize <- lift $ bracket acquire release receive<br>
          let delta = (totalSize - receivedSize)<br>
          if delta > 0 then throwE (NotFullRecv delta) else return ()<br>
       where<br>
         bufferSize = 16384<br>
<br>
         acquire :: IO (IO.Handle,Socket)<br>
         acquire = (,) <$> (IO.openFile name IO.WriteMode)<br>
                       <*> newSocket addr<br>
<br>
         release :: (IO.Handle,Socket) -> IO ()<br>
         release (hdl, sock) = IO.hClose hdl >> close sock<br>
<br>
         receive :: (IO.Handle,Socket) -> IO Int<br>
         receive (hdl, sock) =<br>
             flip execStateT 0 . fix $ \loop -> do<br>
                 mediaData <- lift (B.recv sock bufferSize)<br>
                 unless (B.null mediaData) $ do<br>
                     S.modify' (+ (B.length mediaData))<br>
                     currentSize <- S.get<br>
                     lift $ B.hPut hdl mediaData<br>
                            >> B.send sock (int2BS currentSize)<br>
                            >> swapMVar mvar currentSize<br>
                     loop<br>
<br>
Part of the protocol is that on each `recv` I send the current received<br>
size on network byte order. Hence the B.send line on receive I use this<br>
function:<br>
<br>
     -- | given a number forms a bytestring with each digit on a separated<br>
     -- Word8 in network byte-order<br>
     int2BS :: Int -> B.ByteString<br>
     int2BS i | w <- (fromIntegral i :: Word32) =<br>
         B.pack [ (fromIntegral (shiftR w 24) :: Word8)<br>
               , (fromIntegral (shiftR w 16) :: Word8)<br>
               , (fromIntegral (shiftR w  8) :: Word8)<br>
               , (fromIntegral w             :: Word8)]<br>
<br>
Everything works correctly until around 1/2 of a test transfer (ie in a<br>
file of 340M it gets 170). That first half is gotten in the right order<br>
(I tested with a video and it was playable until the middle). On tinier<br>
files the bug doesn't happen, the file is received completly. I did a<br>
little bit of `strace` and `tcpdump` and I got this<br>
<br>
-- strace -e trace=network -p $client<br>
     (..)<br>
     30439 recvfrom(13,<br>
"\312\255\201\337\376\355\253\r\177\276\204X]8\6\221\301#\361<>\273+\355\5\343B<br>
\333\366\351W"..., 16384, 0, NULL, NULL) = 1380<br>
     30439 sendto(13, "\n\273\31l", 4, 0, NULL, 0) = 4<br>
     30439 recvfrom(13, 0x20023f010, 16384, 0, NULL, NULL) = -1 EAGAIN<br>
(Resource temporarily unavailable)<br>
     30439 recvfrom(13,<br>
"\222llq_H\23\17\275\f}\367\"P4\23\207\312$w\371J\354aW2\243R\32\v\n\251"...,<br>
16384, 0, NULL, NULL) = 1380<br>
     30439 sendto(13, "\n\273\36\320", 4, 0, NULL, 0) = -1 EAGAIN (Resource<br>
temporarily unavailable)<br>
     30438 --- SIGVTALRM {si_signo=SIGVTALRM, si_code=SI_TIMER,<br>
si_timerid=0, si_overrun=0, si_value={int=0, ptr=0}} ---<br>
     30438 --- SIGVTALRM {si_signo=SIGVTALRM, si_code=SI_TIMER,<br>
si_timerid=0, si_overrun=0, si_value={int=0, ptr=0}} ---<br>
     (..)<br>
<br>
-- tcpdump<br>
     05:20:22.788273 IP tapioca.36346 > 198.255.92.74.36103: Flags [.], ack<br>
48004680, win 489, options [nop,nop,TS val 627805332 ecr<br>
675358947,nop,nop,sack 1 {48006060:48066780}], length 0<br>
     05:20:22.975627 IP 198.255.92.74.36103 > tapioca.36346: Flags [.], seq<br>
48004680:48006060, ack 82629, win 0, options [nop,nop,TS val 675359033 ecr<br>
627805248], length 1380<br>
     05:20:23.014991 IP tapioca.36346 > 198.255.92.74.36103: Flags [.], ack<br>
48066780, win 4, options [nop,nop,TS val 627805559 ecr 675359033], length 0<br>
     05:20:23.768012 IP 198.255.92.74.36103 > tapioca.36346: Flags [P.],<br>
seq 48066780:48067292, ack 82629, win 0, options [nop,nop,TS val 675359232<br>
ecr 627805559], length 512<br>
     05:20:23.768143 IP tapioca.36346 > 198.255.92.74.36103: Flags [.], ack<br>
48067292, win 0, options [nop,nop,TS val 627806312 ecr 675359232], length 0<br>
     05:20:24.523397 IP 198.255.92.74.36103 > tapioca.36346: Flags [.], ack<br>
82629, win 0, options [nop,nop,TS val 675359421 ecr 627806312], length 0<br>
<br>
What bothers me is that SIGVTALRM on the strace output. I am not the<br>
greatest unix hacker but that signal is related to settimer and I haven't<br>
explicitly set that up. So I am scratching me head a little. Maybe<br>
somebody has experienced something related with the network package? Do<br>
you notice something on the logs? thanks in advance.<br>
<br>
--<br>
-- Ruben Astudillo<br>
_______________________________________________<br>
Haskell-Cafe mailing list<br>
To (un)subscribe, modify options or view archives go to:<br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe</a><br>
Only members subscribed via the mailman list are allowed to post.</blockquote></div>