Hi,<div><br></div><div>I added the following code to your program:</div><div><br></div><div><br></div><div>import qualified Data.ByteString.Char8 as B</div><div><br></div><div><div>sendMsg = withSocketsDo $ do</div><div>    sock &lt;- socket AF_INET Datagram defaultProtocol</div>


<div>    target &lt;- inet_addr &quot;192.168.2.103&quot; -- put your servers IP here</div><div>    sendTo sock (B.pack &quot;TEST&quot;) $ SockAddrInet 5555 target</div></div><div><br></div><div><br></div><div>On my Windows 7 machine this works fine; the messages are received by the server. It also works if I run the sendMsg program on a Linux VM which lives on a separate IP. </div>


<div>So it seems that it&#39;s not a general bug but rather a problem with your setup, possibly a firewall.</div><div><br><div class="gmail_quote">2012/6/18 Edward Amsden <span dir="ltr">&lt;<a href="mailto:eca7215@cs.rit.edu" target="_blank">eca7215@cs.rit.edu</a>&gt;</span><br>


<blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">Hi all,<br>
<br>
I have the following program, which I&#39;m running using runghc 7.4.1<br>
with HP2012.2 on Windows 7:<br>
<br>
==<br>
{-# LANGUAGE OverloadedStrings #-}<br>
module Main where<br>
<br>
import Network.Socket hiding (send, sendTo, recv, recvFrom)<br>
import Network.Socket.ByteString<br>
import qualified Data.Text as T<br>
import qualified Data.Text.Encoding as T<br>
import qualified <a href="http://Data.Text.IO" target="_blank">Data.Text.IO</a> as T<br>
<br>
port :: String<br>
port = show (5555 :: Int)<br>
<br>
main :: IO ()<br>
main = withSocketsDo $ do<br>
  addrInf:_ &lt;- fmap (filter ((== AF_INET) . addrFamily)) $ getAddrInfo<br>
(Just (defaultHints {addrFlags = [AI_PASSIVE]})) Nothing (Just port)<br>
  putStrLn &quot;Address info: &quot;<br>
  print addrInf<br>
  sock &lt;- socket (addrFamily addrInf) Datagram defaultProtocol<br>
  putStrLn &quot;Socket created&quot;<br>
  bindSocket sock (addrAddress addrInf)<br>
  putStrLn &quot;Socket bound&quot;<br>
  let procMessages =<br>
        do<br>
          (msg, addr) &lt;- recvFrom sock 1024<br>
          let addrTxt = T.pack $ show addr<br>
              msgTxt  = T.decodeUtf8 msg<br>
              outputTxt = T.concat [addrTxt, &quot; says &quot;, msgTxt]<br>
          T.putStrLn outputTxt<br>
        procMessages<br>
  procMessages<br>
==<br>
<br>
I&#39;m trying to receive incoming UDP packets on port 5555.<br>
Unfortunately, when I run the program it does not receive packets. It<br>
prints the address info, and the messages that the socket has been<br>
created and bound. When I run Wireshark I can see that there are<br>
indeed incoming UDP packets arriving on port 5555 (from another<br>
computer on the local network running a proprietary program).<br>
<br>
The other bit of information that may be useful is that the machine<br>
has 2 network interfaces. However, when I replace the Nothing<br>
parameter of getAddrInfo with<br>
(Just &quot;192.168.1.3&quot;) which is the address of the correct NIC, the<br>
behavior is as before.<br>
<br>
Is there something I&#39;m missing?<br>
<br>
_______________________________________________<br>
Haskell-Cafe mailing list<br>
<a href="mailto:Haskell-Cafe@haskell.org" target="_blank">Haskell-Cafe@haskell.org</a><br>
<a href="http://www.haskell.org/mailman/listinfo/haskell-cafe" target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br>
</blockquote></div><br></div>