[Haskell-cafe] Receiving UDP messages on Windows 7
Holger Reinhardt
hreinhardt at gmail.com
Mon Jun 18 17:14:57 CEST 2012
Hi,
I added the following code to your program:
import qualified Data.ByteString.Char8 as B
sendMsg = withSocketsDo $ do
sock <- socket AF_INET Datagram defaultProtocol
target <- inet_addr "192.168.2.103" -- put your servers IP here
sendTo sock (B.pack "TEST") $ SockAddrInet 5555 target
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.
So it seems that it's not a general bug but rather a problem with your
setup, possibly a firewall.
2012/6/18 Edward Amsden <eca7215 at cs.rit.edu>
> Hi all,
>
> I have the following program, which I'm running using runghc 7.4.1
> with HP2012.2 on Windows 7:
>
> ==
> {-# LANGUAGE OverloadedStrings #-}
> module Main where
>
> import Network.Socket hiding (send, sendTo, recv, recvFrom)
> import Network.Socket.ByteString
> import qualified Data.Text as T
> import qualified Data.Text.Encoding as T
> import qualified Data.Text.IO as T
>
> port :: String
> port = show (5555 :: Int)
>
> main :: IO ()
> main = withSocketsDo $ do
> addrInf:_ <- fmap (filter ((== AF_INET) . addrFamily)) $ getAddrInfo
> (Just (defaultHints {addrFlags = [AI_PASSIVE]})) Nothing (Just port)
> putStrLn "Address info: "
> print addrInf
> sock <- socket (addrFamily addrInf) Datagram defaultProtocol
> putStrLn "Socket created"
> bindSocket sock (addrAddress addrInf)
> putStrLn "Socket bound"
> let procMessages =
> do
> (msg, addr) <- recvFrom sock 1024
> let addrTxt = T.pack $ show addr
> msgTxt = T.decodeUtf8 msg
> outputTxt = T.concat [addrTxt, " says ", msgTxt]
> T.putStrLn outputTxt
> procMessages
> procMessages
> ==
>
> I'm trying to receive incoming UDP packets on port 5555.
> Unfortunately, when I run the program it does not receive packets. It
> prints the address info, and the messages that the socket has been
> created and bound. When I run Wireshark I can see that there are
> indeed incoming UDP packets arriving on port 5555 (from another
> computer on the local network running a proprietary program).
>
> The other bit of information that may be useful is that the machine
> has 2 network interfaces. However, when I replace the Nothing
> parameter of getAddrInfo with
> (Just "192.168.1.3") which is the address of the correct NIC, the
> behavior is as before.
>
> Is there something I'm missing?
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20120618/891a0b44/attachment.htm>
More information about the Haskell-Cafe
mailing list