Hi,
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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe