module Control.Remote.Monad.JSON.Router
(
router
, ReceiveAPI(..)
, Call(..)
, transport
, methodNotFound
, invalidParams
, parseError
) where
import Control.Monad.Catch
import Control.Remote.Monad.JSON.Types
import Control.Natural
import Data.Aeson
import Data.Text(Text)
import Data.Typeable
import qualified Data.Vector as V
data Call :: * -> * where
CallMethod :: Text -> Args -> Call Value
CallNotification :: Text -> Args -> Call ()
router :: MonadCatch m
=> (forall a. [m a] -> m [a])
-> (Call :~> m) -> (ReceiveAPI :~> m)
router s f = nat $ \ case
(Receive v@(Object {})) -> simpleRouter f v
(Receive (Array a))
| V.null a -> return $ Just $ invalidRequest
| otherwise -> do
rs <- s (map (simpleRouter f) $ V.toList a)
case [ v | Just v <- rs ] of
[] -> return Nothing
vs -> return (Just (toJSON vs))
(Receive _) -> return $ Just $ invalidRequest
simpleRouter :: forall m . MonadCatch m
=> (Call :~> m)
-> Value -> m (Maybe Value)
simpleRouter (Nat f) v = case call <$> fromJSON v of
Success m -> m
Error _ -> return $ Just $ invalidRequest
where
call :: JSONCall -> m (Maybe Value)
call (MethodCall (Method nm args) tag) = (do
r <- f (CallMethod nm args :: Call Value)
return $ Just $ object
[ "jsonrpc" .= ("2.0" :: Text)
, "result" .= toJSON r
, "id" .= tag
]) `catches`
[ Handler $ \ (_ :: MethodNotFound) ->
return $ Just $ toJSON
$ errorResponse (32601) "Method not found" tag
, Handler $ \ (_ :: InvalidParams) ->
return $ Just $ toJSON
$ errorResponse (32602) "Invalid params" tag
, Handler $ \ (_ :: SomeException) ->
return $ Just $ toJSON
$ errorResponse (32603) "Internal error" tag
]
call (NotificationCall (Notification nm args)) =
(f (CallNotification nm args) >> return Nothing) `catchAll` \ _ -> return Nothing
transport :: (Monad f) => (ReceiveAPI :~> f) -> (SendAPI :~> f)
transport f = nat $ \ case
Sync v -> do
r <- f # Receive v
case r of
Nothing -> fail "no result returned in transport"
Just v0 -> return v0
Async v -> do
r <- f # Receive v
case r of
Nothing -> return ()
Just v0 -> fail $ "unexpected result in transport: " ++ show v0
errorResponse :: Int -> Text -> Value -> Value
errorResponse code msg theId = toJSON $
ErrorResponse (ErrorMessage code msg) theId
invalidRequest :: Value
invalidRequest = errorResponse (32600) "Invalid Request" Null
parseError :: Value
parseError = errorResponse (32700) "Parse error" Null
data MethodNotFound = MethodNotFound
deriving (Show, Typeable)
instance Exception MethodNotFound
methodNotFound :: MonadThrow m => m a
methodNotFound = throwM $ MethodNotFound
data InvalidParams = InvalidParams
deriving (Show, Typeable)
instance Exception InvalidParams
invalidParams :: MonadThrow m => m a
invalidParams = throwM $ InvalidParams