module Sound.OSC.Transport.FD.UDP where
import Control.Monad
import qualified Network.Socket as N
import qualified Network.Socket.ByteString as C
import Sound.OSC.Class
import Sound.OSC.Coding
import Sound.OSC.Type
import Sound.OSC.Transport.FD
data UDP = UDP {udpSocket :: N.Socket}
udpPort :: Integral n => UDP -> IO n
udpPort (UDP fd) = fmap fromIntegral (N.socketPort fd)
instance Transport UDP where
sendOSC (UDP fd) msg = void (C.send fd (encodeOSC msg))
recvPacket (UDP fd) = liftM decodePacket (C.recv fd 8192)
close (UDP fd) = N.sClose fd
udp_socket :: (N.Socket -> N.SockAddr -> IO ()) -> String -> Int -> IO UDP
udp_socket f host port = do
fd <- N.socket N.AF_INET N.Datagram 0
a <- N.inet_addr host
let sa = N.SockAddrInet (fromIntegral port) a
f fd sa
return (UDP fd)
openUDP :: String -> Int -> IO UDP
openUDP = udp_socket N.connect
udpServer :: String -> Int -> IO UDP
udpServer = udp_socket N.bindSocket
sendTo :: OSC o => UDP -> o -> N.SockAddr -> IO ()
sendTo (UDP fd) o a = do
void (C.sendTo fd (encodeOSC o) a)
recvFrom :: UDP -> IO (Packet, N.SockAddr)
recvFrom (UDP fd) = do
(s,a) <- C.recvFrom fd 8192
return (decodePacket s,a)