module Network.MessagePack.Types.Spec ( Request , Response , packRequest , packResponse , unpackRequest , unpackResponse ) where import Control.Monad.Validate (runValidate) import qualified Data.ByteString.Lazy as L import qualified Data.List as List import Data.MessagePack (DecodeError, MessagePack, Object, defaultConfig, fromObjectWith, pack) type Request ix = (Int, Int, ix, [Object]) type Response = (Int, Int, Object, Object) packRequest :: (Eq mth, MessagePack mth) => [mth] -> Request mth -> L.ByteString packRequest :: [mth] -> Request mth -> ByteString packRequest [] Request mth req = Request mth -> ByteString forall a. MessagePack a => a -> ByteString pack Request mth req packRequest [mth] mths req :: Request mth req@(Int rtype, Int msgid, mth mth, [Object] obj) = case mth -> [mth] -> Maybe Int forall a. Eq a => a -> [a] -> Maybe Int List.elemIndex mth mth [mth] mths of Maybe Int Nothing -> Request mth -> ByteString forall a. MessagePack a => a -> ByteString pack Request mth req Just Int ix -> (Int, Int, Int, [Object]) -> ByteString forall a. MessagePack a => a -> ByteString pack (Int rtype, Int msgid, Int ix, [Object] obj) packResponse :: Response -> L.ByteString packResponse :: Response -> ByteString packResponse = Response -> ByteString forall a. MessagePack a => a -> ByteString pack unpackResponse :: Object -> Either DecodeError Response unpackResponse :: Object -> Either DecodeError Response unpackResponse = Validate DecodeError Response -> Either DecodeError Response forall e a. Validate e a -> Either e a runValidate (Validate DecodeError Response -> Either DecodeError Response) -> (Object -> Validate DecodeError Response) -> Object -> Either DecodeError Response forall b c a. (b -> c) -> (a -> b) -> a -> c . Config -> Object -> Validate DecodeError Response forall a (m :: * -> *). (MessagePack a, Applicative m, Monad m, MonadValidate DecodeError m) => Config -> Object -> m a fromObjectWith Config defaultConfig unpackRequest :: MessagePack ix => Object -> Either DecodeError (Request ix) unpackRequest :: Object -> Either DecodeError (Request ix) unpackRequest = Validate DecodeError (Request ix) -> Either DecodeError (Request ix) forall e a. Validate e a -> Either e a runValidate (Validate DecodeError (Request ix) -> Either DecodeError (Request ix)) -> (Object -> Validate DecodeError (Request ix)) -> Object -> Either DecodeError (Request ix) forall b c a. (b -> c) -> (a -> b) -> a -> c . Config -> Object -> Validate DecodeError (Request ix) forall a (m :: * -> *). (MessagePack a, Applicative m, Monad m, MonadValidate DecodeError m) => Config -> Object -> m a fromObjectWith Config defaultConfig