{-# LANGUAGE Safe #-}
module Network.MessagePack.Types.Client
  ( RpcType (..)
  , call
  ) where

import           Data.MessagePack.Types (MessagePack (toObject), Object)
import           Data.Text              (Text)


class RpcType r where
  rpcc :: Text -> [Object] -> r


instance (MessagePack o, RpcType r) => RpcType (o -> r) where
  rpcc :: Text -> [Object] -> o -> r
rpcc Text
name [Object]
args o
arg = Text -> [Object] -> r
forall r. RpcType r => Text -> [Object] -> r
rpcc Text
name (o -> Object
forall a. MessagePack a => a -> Object
toObject o
arg Object -> [Object] -> [Object]
forall a. a -> [a] -> [a]
: [Object]
args)
  {-# INLINE rpcc #-}


-- | Call an RPC Method
call :: RpcType a => Text -> a
call :: Text -> a
call Text
name = Text -> [Object] -> a
forall r. RpcType r => Text -> [Object] -> r
rpcc Text
name []
{-# INLINE call #-}