hosc-0.20: Haskell Open Sound Control
Safe HaskellSafe-Inferred
LanguageHaskell2010

Sound.Osc.Transport.Fd.Udp

Description

Osc over Udp implementation.

Synopsis

Documentation

newtype Udp Source #

The Udp transport handle data type.

Constructors

Udp 

Fields

Instances

Instances details
Transport Udp Source #

Udp is an instance of Transport.

Instance details

Defined in Sound.Osc.Transport.Fd.Udp

udpPort :: Integral n => Udp -> IO n Source #

Return the port number associated with the Udp socket.

udp_send_data :: Udp -> ByteString -> IO () Source #

Send data over Udp using send.

udp_sendAll_data :: Udp -> ByteString -> IO () Source #

Send data over Udp using sendAll.

udp_send_packet :: Udp -> Packet -> IO () Source #

Send packet over Udp.

udp_recv_packet :: Udp -> IO Packet Source #

Receive packet over Udp.

udp_close :: Udp -> IO () Source #

Close Udp.

with_udp :: IO Udp -> (Udp -> IO t) -> IO t Source #

Bracket Udp communication.

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.

udpServer :: String -> Int -> IO Udp Source #

Trivial Udp server socket.

import Control.Concurrent 
let u0 = udpServer "127.0.0.1" 57300
t0 <- forkIO (Fd.withTransport u0 (\fd -> forever (Fd.recvMessage fd >>= print >> print "Received message, continuing")))
killThread t0
let u1 = openUdp "127.0.0.1" 57300
Fd.withTransport u1 (\fd -> Fd.sendMessage fd (Packet.message "/n" []))

udp_server :: Int -> IO Udp Source #

Variant of udpServer that doesn't require the host address.

sendTo :: Udp -> Packet -> SockAddr -> IO () Source #

Send to specified address using 'C.sendAllTo.

recvFrom :: Udp -> IO (Packet, SockAddr) Source #

Recv variant to collect message source address.