[Haskell-cafe] UDP
John Van Enk
vanenkj at gmail.com
Sat Jan 31 16:41:57 EST 2009
Try something like this:
module Main where
import Network.Socket
main = withSocketsDo $ do
-- Make a UDP socket
s <- socket AF_INET Datagram defaultProtocol
-- We want to listen on all interfaces (0.0.0.0)
bindAddr <- inet_addr "0.0.0.0"
-- Bind to 0.0.0.0:30000
bindSocket s (SockAddrInet 30000 bindAddr)
-- Read a message of max length 1000 from some one
(msg,len,from) <- recvFrom s 1000
putStrLn $ "Got the following message from " ++ (show from)
putStrLn msg
Does this help? As Stephan said, you missed the bind step.
/jve
On Sun, Jan 25, 2009 at 11:22 AM, Andrew Coppin <andrewcoppin at btinternet.com
> wrote:
> I'm trying to write a simple program that involves UDP. I was hoping
> something like this would work:
>
> module Main where
>
> import Network.Socket
>
> main = withSocketsDo main2
>
> main2 = do
> s <- socket AF_INET Datagram defaultProtocol
> putStrLn "Waiting..."
> x <- recv s 100
> putStrLn x
>
> Unfortunately, that doesn't work at all. It immediately throws an exception
> ("unknown error"). But then, the whole module seems to be completely
> undocumented. I managed to find a tiny amount of info online about the
> underlying C API, but I still don't get how the Haskell interface is
> supposed to be used. Any hints?
>
> _______________________________________________
> 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/20090131/c708fd3a/attachment.htm
More information about the Haskell-Cafe
mailing list