module Sound.OSC.Transport.FD.UDP where
import Control.Exception 
import Data.Bifunctor 
import qualified Network.Socket as N 
import qualified Network.Socket.ByteString as C 
import qualified Sound.OSC.Coding.Decode.Binary as Binary 
import qualified Sound.OSC.Coding.Encode.Builder as Builder 
import qualified Sound.OSC.Packet as Packet 
import qualified Sound.OSC.Transport.FD as FD 
newtype UDP = UDP {UDP -> Socket
udpSocket :: N.Socket}
udpPort :: Integral n => UDP -> IO n
udpPort :: UDP -> IO n
udpPort = (PortNumber -> n) -> IO PortNumber -> IO n
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PortNumber -> n
forall a b. (Integral a, Num b) => a -> b
fromIntegral (IO PortNumber -> IO n) -> (UDP -> IO PortNumber) -> UDP -> IO n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> IO PortNumber
N.socketPort (Socket -> IO PortNumber)
-> (UDP -> Socket) -> UDP -> IO PortNumber
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UDP -> Socket
udpSocket
upd_send_packet :: UDP -> Packet.Packet -> IO ()
upd_send_packet :: UDP -> Packet -> IO ()
upd_send_packet (UDP Socket
fd) Packet
p = Socket -> ByteString -> IO ()
C.sendAll Socket
fd (Packet -> ByteString
Builder.encodePacket_strict Packet
p)
udp_recv_packet :: UDP -> IO Packet.Packet
udp_recv_packet :: UDP -> IO Packet
udp_recv_packet (UDP Socket
fd) = (ByteString -> Packet) -> IO ByteString -> IO Packet
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Packet
Binary.decodePacket_strict (Socket -> Int -> IO ByteString
C.recv Socket
fd Int
8192)
udp_close :: UDP -> IO ()
udp_close :: UDP -> IO ()
udp_close (UDP Socket
fd) = Socket -> IO ()
N.close Socket
fd
instance FD.Transport UDP where
   sendPacket :: UDP -> Packet -> IO ()
sendPacket = UDP -> Packet -> IO ()
upd_send_packet
   recvPacket :: UDP -> IO Packet
recvPacket = UDP -> IO Packet
udp_recv_packet
   close :: UDP -> IO ()
close = UDP -> IO ()
udp_close
with_udp :: IO UDP -> (UDP -> IO t) -> IO t
with_udp :: IO UDP -> (UDP -> IO t) -> IO t
with_udp IO UDP
u = IO UDP -> (UDP -> IO ()) -> (UDP -> IO t) -> IO t
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket IO UDP
u UDP -> IO ()
udp_close
udp_socket :: (N.Socket -> N.SockAddr -> IO ()) -> String -> Int -> IO UDP
udp_socket :: (Socket -> SockAddr -> IO ()) -> String -> Int -> IO UDP
udp_socket Socket -> SockAddr -> IO ()
f String
host Int
port = do
  Socket
fd <- Family -> SocketType -> ProtocolNumber -> IO Socket
N.socket Family
N.AF_INET SocketType
N.Datagram ProtocolNumber
0
  let hints :: AddrInfo
hints = AddrInfo
N.defaultHints {addrFamily :: Family
N.addrFamily = Family
N.AF_INET} 
  AddrInfo
i:[AddrInfo]
_ <- Maybe AddrInfo -> Maybe String -> Maybe String -> IO [AddrInfo]
N.getAddrInfo (AddrInfo -> Maybe AddrInfo
forall a. a -> Maybe a
Just AddrInfo
hints) (String -> Maybe String
forall a. a -> Maybe a
Just String
host) (String -> Maybe String
forall a. a -> Maybe a
Just (Int -> String
forall a. Show a => a -> String
show Int
port))
  let sa :: SockAddr
sa = AddrInfo -> SockAddr
N.addrAddress AddrInfo
i
  Socket -> SockAddr -> IO ()
f Socket
fd SockAddr
sa
  UDP -> IO UDP
forall (m :: * -> *) a. Monad m => a -> m a
return (Socket -> UDP
UDP Socket
fd)
set_udp_opt :: N.SocketOption -> Int -> UDP -> IO ()
set_udp_opt :: SocketOption -> Int -> UDP -> IO ()
set_udp_opt SocketOption
k Int
v (UDP Socket
s) = Socket -> SocketOption -> Int -> IO ()
N.setSocketOption Socket
s SocketOption
k Int
v
get_udp_opt :: N.SocketOption -> UDP -> IO Int
get_udp_opt :: SocketOption -> UDP -> IO Int
get_udp_opt SocketOption
k (UDP Socket
s) = Socket -> SocketOption -> IO Int
N.getSocketOption Socket
s SocketOption
k
openUDP :: String -> Int -> IO UDP
openUDP :: String -> Int -> IO UDP
openUDP = (Socket -> SockAddr -> IO ()) -> String -> Int -> IO UDP
udp_socket Socket -> SockAddr -> IO ()
N.connect
udpServer :: String -> Int -> IO UDP
udpServer :: String -> Int -> IO UDP
udpServer = (Socket -> SockAddr -> IO ()) -> String -> Int -> IO UDP
udp_socket Socket -> SockAddr -> IO ()
N.bind
udp_server :: Int -> IO UDP
udp_server :: Int -> IO UDP
udp_server Int
p = do
  let hints :: AddrInfo
hints =
        AddrInfo
N.defaultHints
        {addrFamily :: Family
N.addrFamily = Family
N.AF_INET 
        ,addrFlags :: [AddrInfoFlag]
N.addrFlags = [AddrInfoFlag
N.AI_PASSIVE,AddrInfoFlag
N.AI_NUMERICSERV]
        ,addrSocketType :: SocketType
N.addrSocketType = SocketType
N.Datagram}
  AddrInfo
a:[AddrInfo]
_ <- Maybe AddrInfo -> Maybe String -> Maybe String -> IO [AddrInfo]
N.getAddrInfo (AddrInfo -> Maybe AddrInfo
forall a. a -> Maybe a
Just AddrInfo
hints) Maybe String
forall a. Maybe a
Nothing (String -> Maybe String
forall a. a -> Maybe a
Just (Int -> String
forall a. Show a => a -> String
show Int
p))
  Socket
s <- Family -> SocketType -> ProtocolNumber -> IO Socket
N.socket (AddrInfo -> Family
N.addrFamily AddrInfo
a) (AddrInfo -> SocketType
N.addrSocketType AddrInfo
a) (AddrInfo -> ProtocolNumber
N.addrProtocol AddrInfo
a)
  Socket -> SocketOption -> Int -> IO ()
N.setSocketOption Socket
s SocketOption
N.ReuseAddr Int
1
  Socket -> SockAddr -> IO ()
N.bind Socket
s (AddrInfo -> SockAddr
N.addrAddress AddrInfo
a)
  UDP -> IO UDP
forall (m :: * -> *) a. Monad m => a -> m a
return (Socket -> UDP
UDP Socket
s)
sendTo :: UDP -> Packet.Packet -> N.SockAddr -> IO ()
sendTo :: UDP -> Packet -> SockAddr -> IO ()
sendTo (UDP Socket
fd) Packet
p = Socket -> ByteString -> SockAddr -> IO ()
C.sendAllTo Socket
fd (Packet -> ByteString
Builder.encodePacket_strict Packet
p)
recvFrom :: UDP -> IO (Packet.Packet, N.SockAddr)
recvFrom :: UDP -> IO (Packet, SockAddr)
recvFrom (UDP Socket
fd) = ((ByteString, SockAddr) -> (Packet, SockAddr))
-> IO (ByteString, SockAddr) -> IO (Packet, SockAddr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((ByteString -> Packet)
-> (ByteString, SockAddr) -> (Packet, SockAddr)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first ByteString -> Packet
Binary.decodePacket_strict) (Socket -> Int -> IO (ByteString, SockAddr)
C.recvFrom Socket
fd Int
8192)