{- | Monad class for monads that are able to do or simulate communication via Open Sound Control. -} module Sound.OpenSoundControl.Transport.Monad ( C, send, recv, waitFor, wait, ) where import qualified Sound.OpenSoundControl.Transport as Trans import Sound.OpenSoundControl.Transport (Transport) import Sound.OpenSoundControl.OSC (OSC(Message)) import Control.Monad.Trans.Reader (ReaderT(ReaderT)) import Control.Monad.IO.Class (MonadIO, liftIO, ) import Data.Maybe.HT (toMaybe, ) class Monad m => C m where -- | Encode and send an OSC packet. send :: OSC -> m () -- | Receive and decode an OSC packet. recv :: m OSC instance (Transport t, MonadIO io) => C (ReaderT t io) where send osc = ReaderT $ liftIO . flip Trans.send osc recv = ReaderT $ liftIO . Trans.recv -- Does the OSC message have the specified address. hasAddress :: String -> OSC -> Bool hasAddress x (Message y _) = x == y hasAddress _ _ = False -- Repeat action until function does not give Nothing when applied to result. untilM :: Monad m => (a -> Maybe b) -> m a -> m b untilM f act = let go = maybe go return . f =<< act in go -- | Wait for an OSC message where the supplied function does not give -- Nothing, discarding intervening messages. waitFor :: C m => (OSC -> Maybe a) -> m a waitFor f = untilM f recv -- | A 'waitFor' for variant matching on address string of messages. wait :: C m => String -> m OSC wait s = waitFor (\o -> toMaybe (hasAddress s o) o)