module Sound.Osc.Transport.Fd where
import Control.Exception
import Data.List
import Data.Maybe
import Sound.Osc.Datum
import Sound.Osc.Packet
import qualified Sound.Osc.Wait as Wait
class Transport t where
sendPacket :: t -> Packet -> IO ()
recvPacket :: t -> IO Packet
close :: t -> IO ()
withTransport :: Transport t => IO t -> (t -> IO a) -> IO a
withTransport :: forall t a. Transport t => IO t -> (t -> IO a) -> IO a
withTransport IO t
u = forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket IO t
u forall t. Transport t => t -> IO ()
close
sendMessage :: Transport t => t -> Message -> IO ()
sendMessage :: forall t. Transport t => t -> Message -> IO ()
sendMessage t
t = forall t. Transport t => t -> Packet -> IO ()
sendPacket t
t forall b c a. (b -> c) -> (a -> b) -> a -> c
. Message -> Packet
Packet_Message
sendBundle :: Transport t => t -> Bundle -> IO ()
sendBundle :: forall t. Transport t => t -> Bundle -> IO ()
sendBundle t
t = forall t. Transport t => t -> Packet -> IO ()
sendPacket t
t forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bundle -> Packet
Packet_Bundle
recvBundle :: (Transport t) => t -> IO Bundle
recvBundle :: forall t. Transport t => t -> IO Bundle
recvBundle = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Packet -> Bundle
packet_to_bundle forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. Transport t => t -> IO Packet
recvPacket
recvMessage :: (Transport t) => t -> IO (Maybe Message)
recvMessage :: forall t. Transport t => t -> IO (Maybe Message)
recvMessage = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Packet -> Maybe Message
packet_to_message forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. Transport t => t -> IO Packet
recvPacket
recvMessages :: (Transport t) => t -> IO [Message]
recvMessages :: forall t. Transport t => t -> IO [Message]
recvMessages = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Packet -> [Message]
packetMessages forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. Transport t => t -> IO Packet
recvPacket
waitUntil :: (Transport t) => t -> (Packet -> Bool) -> IO Packet
waitUntil :: forall t. Transport t => t -> (Packet -> Bool) -> IO Packet
waitUntil t
t Packet -> Bool
f = forall (m :: * -> *) a. Monad m => (a -> Bool) -> m a -> m a
Wait.untilPredicate Packet -> Bool
f (forall t. Transport t => t -> IO Packet
recvPacket t
t)
waitFor :: (Transport t) => t -> (Packet -> Maybe a) -> IO a
waitFor :: forall t a. Transport t => t -> (Packet -> Maybe a) -> IO a
waitFor t
t Packet -> Maybe a
f = forall (m :: * -> *) a b. Monad m => (a -> Maybe b) -> m a -> m b
Wait.untilMaybe Packet -> Maybe a
f (forall t. Transport t => t -> IO Packet
recvPacket t
t)
waitImmediate :: Transport t => t -> IO Packet
waitImmediate :: forall t. Transport t => t -> IO Packet
waitImmediate t
t = forall t. Transport t => t -> (Packet -> Bool) -> IO Packet
waitUntil t
t Packet -> Bool
packet_is_immediate
waitMessage :: Transport t => t -> IO Message
waitMessage :: forall t. Transport t => t -> IO Message
waitMessage t
t = forall t a. Transport t => t -> (Packet -> Maybe a) -> IO a
waitFor t
t Packet -> Maybe Message
packet_to_message
waitAddress :: Transport t => t -> Address_Pattern -> IO Packet
waitAddress :: forall t. Transport t => t -> Address_Pattern -> IO Packet
waitAddress t
t Address_Pattern
s =
let f :: Packet -> Maybe Packet
f Packet
o = if Address_Pattern -> Packet -> Bool
packet_has_address Address_Pattern
s Packet
o then forall a. a -> Maybe a
Just Packet
o else forall a. Maybe a
Nothing
in forall t a. Transport t => t -> (Packet -> Maybe a) -> IO a
waitFor t
t Packet -> Maybe Packet
f
waitReply :: Transport t => t -> Address_Pattern -> IO Message
waitReply :: forall t. Transport t => t -> Address_Pattern -> IO Message
waitReply t
t Address_Pattern
s =
let f :: Packet -> Message
f = forall a. a -> Maybe a -> a
fromMaybe (forall a. HasCallStack => Address_Pattern -> a
error Address_Pattern
"waitReply: message not located?") forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (Address_Pattern -> Message -> Bool
message_has_address Address_Pattern
s) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Packet -> [Message]
packetMessages
in forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Packet -> Message
f (forall t. Transport t => t -> Address_Pattern -> IO Packet
waitAddress t
t Address_Pattern
s)
waitDatum :: Transport t => t -> Address_Pattern -> IO [Datum]
waitDatum :: forall t. Transport t => t -> Address_Pattern -> IO [Datum]
waitDatum t
t = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Message -> [Datum]
messageDatum forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. Transport t => t -> Address_Pattern -> IO Message
waitReply t
t