module Network.ZRE.Lib where import Control.Applicative import Control.Monad import Data.ByteString (ByteString) import qualified Data.ByteString.Char8 import Data.ZRE (Group) import Network.ZRE.Types zrecvWithShout :: Group -> (ByteString -> ZRE ()) -> ZRE () zrecvWithShout :: Group -> (ByteString -> ZRE ()) -> ZRE () zrecvWithShout Group group ByteString -> ZRE () f = do Event e <- ZRE Event zrecv case Event e of Shout UUID _ Group forGroup Content content UTCTime _time | Group forGroup forall a. Eq a => a -> a -> Bool == Group group -> ByteString -> ZRE () f (Content -> ByteString Data.ByteString.Char8.concat Content content) Event _ | Bool otherwise -> forall (m :: * -> *) a. Monad m => a -> m a return () zrecvShouts :: Group -> (ByteString -> ZRE ()) -> ZRE () zrecvShouts :: Group -> (ByteString -> ZRE ()) -> ZRE () zrecvShouts Group group ByteString -> ZRE () fn = forall (f :: * -> *) a b. Applicative f => f a -> f b forever forall a b. (a -> b) -> a -> b $ Group -> (ByteString -> ZRE ()) -> ZRE () zrecvWithShout Group group ByteString -> ZRE () fn zrecvShoutsDecode :: Group -> (ByteString -> Either String decoded) -> (Either String decoded -> ZRE ()) -> ZRE () zrecvShoutsDecode :: forall decoded. Group -> (ByteString -> Either String decoded) -> (Either String decoded -> ZRE ()) -> ZRE () zrecvShoutsDecode Group group ByteString -> Either String decoded decFn Either String decoded -> ZRE () handler = Group -> (ByteString -> ZRE ()) -> ZRE () zrecvShouts Group group forall a b. (a -> b) -> a -> b $ Either String decoded -> ZRE () handler forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> Either String decoded decFn decodeShouts :: (Monad m, Alternative m) => (Event -> Either String decoded) -> (Either String decoded -> ZRE ()) -> Event -> m (ZRE ()) decodeShouts :: forall (m :: * -> *) decoded. (Monad m, Alternative m) => (Event -> Either String decoded) -> (Either String decoded -> ZRE ()) -> Event -> m (ZRE ()) decodeShouts Event -> Either String decoded fn Either String decoded -> ZRE () action Event msg = do forall (f :: * -> *). Alternative f => Bool -> f () guard forall a b. (a -> b) -> a -> b $ Event -> Bool isShout Event msg forall (m :: * -> *) a. Monad m => a -> m a return forall a b. (a -> b) -> a -> b $ ZRE Event readZ forall (m :: * -> *) a b. Monad m => m a -> m b -> m b >> (Either String decoded -> ZRE () action forall b c a. (b -> c) -> (a -> b) -> a -> c . Event -> Either String decoded fn forall a b. (a -> b) -> a -> b $ Event msg) isShout :: Event -> Bool isShout :: Event -> Bool isShout (Shout UUID _uuid Group _group Content _content UTCTime _time) = Bool True isShout Event _ = Bool False isGroupMsg :: Group -> Event -> Bool isGroupMsg :: Group -> Event -> Bool isGroupMsg Group group (Shout UUID _uuid Group g Content _content UTCTime _time) = Group g forall a. Eq a => a -> a -> Bool == Group group isGroupMsg Group _ Event _ = Bool False (==>) :: (Monad m, Alternative m) => (t -> Bool) -> b -> t -> m b ==> :: forall (m :: * -> *) t b. (Monad m, Alternative m) => (t -> Bool) -> b -> t -> m b (==>) t -> Bool f b act = forall (m :: * -> *) t b. (Monad m, Alternative m) => (t -> Bool) -> b -> t -> m b iff t -> Bool f b act iff :: (Monad m, Alternative m) => (t -> Bool) -> b -> t -> m b iff :: forall (m :: * -> *) t b. (Monad m, Alternative m) => (t -> Bool) -> b -> t -> m b iff t -> Bool f b act t msg = do forall (f :: * -> *). Alternative f => Bool -> f () guard forall a b. (a -> b) -> a -> b $ t -> Bool f t msg forall (m :: * -> *) a. Monad m => a -> m a return forall a b. (a -> b) -> a -> b $ b act match :: [Event -> Maybe (ZRE ())] -> ZRE () match :: [Event -> Maybe (ZRE ())] -> ZRE () match [Event -> Maybe (ZRE ())] acts = do Event msg <- ZRE Event readZ [Event -> Maybe (ZRE ())] -> Event -> ZRE () go [Event -> Maybe (ZRE ())] acts Event msg where go :: [Event -> Maybe (ZRE ())] -> Event -> ZRE () go (Event -> Maybe (ZRE ()) act:[Event -> Maybe (ZRE ())] rest) Event m = do case Event -> Maybe (ZRE ()) act Event m of Maybe (ZRE ()) Nothing -> [Event -> Maybe (ZRE ())] -> Event -> ZRE () go [Event -> Maybe (ZRE ())] rest Event m Just ZRE () a -> Event -> ZRE () unReadZ Event m forall (m :: * -> *) a b. Monad m => m a -> m b -> m b >> ZRE () a go [] Event _ = forall (m :: * -> *) a. Monad m => a -> m a return ()