Safe Haskell | None |
---|---|
Language | Haskell98 |
OSC over UDP implementation.
- data UDP = UDP {}
- udpPort :: Integral n => UDP -> IO n
- udp_socket :: (Socket -> SockAddr -> IO ()) -> String -> Int -> IO UDP
- set_udp_opt :: SocketOption -> Int -> UDP -> IO ()
- get_udp_opt :: SocketOption -> UDP -> IO Int
- openUDP :: String -> Int -> IO UDP
- udpServer :: String -> Int -> IO UDP
- sendTo :: OSC o => UDP -> o -> SockAddr -> IO ()
- recvFrom :: UDP -> IO (Packet, SockAddr)
Documentation
The UDP transport handle data type.
udp_socket :: (Socket -> SockAddr -> IO ()) -> String -> Int -> IO UDP Source #
Create and initialise UDP socket.
set_udp_opt :: SocketOption -> Int -> UDP -> IO () Source #
Set option, ie. Broadcast
or RecvTimeOut
.
get_udp_opt :: SocketOption -> UDP -> IO Int Source #
Get option.
openUDP :: String -> Int -> IO UDP Source #
Make a UDP
connection.
let t = openUDP "127.0.0.1" 57110 in withTransport t (\fd -> recvT 0.5 fd >>= print)
udpServer :: String -> Int -> IO UDP Source #
Trivial UDP
server socket.
import Control.Concurrent
let {f fd = forever (recvMessage fd >>= print) ;t = udpServer "127.0.0.1" 57300} in void (forkIO (withTransport t f))
let t = openUDP "127.0.0.1" 57300 in withTransport t (\fd -> sendMessage fd (message "/n" []))