Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Custom JSON errors for Servant-server

When using servant, I'd like to return all errors as JSON. Currently, if a request fails to parse, I see an error message like this, returned as plain text

Failed reading: not a valid json value

Instead I would like to return this as application/json

{"error":"Failed reading: not a valid json value"}

How can I do this? The docs say ServantErr is the default error type, and I can certainly respond with custom errors inside my handlers, but if parsing fails I don't see how I can return a custom error.

like image 997
Sean Clark Hess Avatar asked Jan 19 '17 23:01

Sean Clark Hess


People also ask

What is JSON-server and how to use it?

In case you don’t know, json-server allows you to run a fake HTTP server with zero coding in no time. This is a common solution to allow UI team to work while REST APIs are being developed by the backend team. To use json-server, you need to install it on your machine using the following command.

How to use JSON-server with Curl?

The way json-server works is that it needs a db.json with some data. You can run fake HTTP server by running following command. You can view all the preferences object by using cURL or something similar. You got all the three records. To view a specific record i.e. record with appId 1 you will be expecting that you could make following cURL call.

How to create demo REST JSON webservice with npm?

JSON Server is a Node Module that you can use to create demo rest json webservice in less than a minute. All you need is a JSON file for sample data. You should have NPM installed on your machine. If not, then refer this post to install NPM.


1 Answers

First, some language extensions

{-# LANGUAGE FlexibleContexts      #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings     #-}
{-# LANGUAGE ScopedTypeVariables   #-}
{-# LANGUAGE TypeFamilies          #-}
{-# LANGUAGE TypeOperators         #-}
{-# LANGUAGE UndecidableInstances  #-}
{-# LANGUAGE ViewPatterns          #-}

Now then

Unfortunately this is more difficult than it should be. Servant, while well-designed and the composition of small logical parts, is very opinionated about how HTTP services should operate. The default implementation of ReqBody, which you are probably using, is hard-coded to spit out a text string.

However, we can switch out ReqBody for our own data type:

module Body where

import Control.Monad.Trans (liftIO)
import Data.Proxy (Proxy(..))
import Network.Wai (lazyRequestBody)

import Data.Aeson
import Servant.API
import Servant.Server
import Servant.Server.Internal

data Body a
instance (FromJSON a, HasServer api context) => HasServer (Body a :> api) context where
  type ServerT (Body a :> api) m = a -> ServerT api m

  route Proxy context subserver =
    route (Proxy :: Proxy api) context (addBodyCheck subserver (withRequest bodyCheck))
    where
      bodyCheck request = do
        body <- liftIO (lazyRequestBody request)
        case eitherDecode body of
          Left (BodyError -> e) ->
            delayedFailFatal err400 { errBody = encode e }
          Right v ->
            return v

In this very brief amount of code a lot is happening:

  • We are teaching the servant-server package on how to handle our new datatype when it appears in the type resolution for serve (Proxy :: Proxy (Body foo :> bar)) server.

  • We have ripped most of the code from the v0.8.1 release of ReqBody.

  • We are adding a function to the pipeline that processes request bodies.

  • In it, we attempt to decode to the a parameter of Body. On failure, we spit out a JSON blob and an HTTP 400.

  • We are entirely ignoring content-type headers here, for brevity.

Here is the type of the JSON blob:

newtype BodyError = BodyError String
instance ToJSON BodyError where
  toJSON (BodyError b) = object ["error" .= b]

Most of this machinery is internal to servant-server and underdocumented and rather fragile. For example, already I see that the code diverges on master branch and the arity of my addBodyCheck has changed.

Though the Servant project is still quite young and remarkably ambitious, I have to say that the aesthetics and robustness of this solution are definitely underwhelming.

To test this

We will need a Main module:

{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE TypeOperators         #-}
module Main where
import Data.Proxy (Proxy(..))
import Network.Wai.Handler.Warp (run)
import Servant.API
import Servant.Server

import Body

type API = Body [Int] :> Post '[JSON] [Int]

server :: Server API
server = pure

main :: IO ()
main = do
  putStrLn "running on port 8000"
  run 8000 (serve (Proxy :: Proxy API) server)

And a shell:

~ ❯❯❯ curl -i -XPOST 'http://localhost:8000/'
HTTP/1.1 400 Bad Request
Transfer-Encoding: chunked
Date: Fri, 20 Jan 2017 01:18:57 GMT
Server: Warp/3.2.9

{"error":"Error in $: not enough input"}%

~ ❯❯❯ curl -id 'hey' -XPOST 'http://localhost:8000/'
HTTP/1.1 400 Bad Request
Transfer-Encoding: chunked
Date: Fri, 20 Jan 2017 01:19:02 GMT
Server: Warp/3.2.9

{"error":"Error in $: Failed reading: not a valid json value"}%

~ ❯❯❯ curl -id '[1,2,3]' -XPOST 'http://localhost:8000/'
HTTP/1.1 200 OK
Transfer-Encoding: chunked
Date: Fri, 20 Jan 2017 01:19:07 GMT
Server: Warp/3.2.9
Content-Type: application/json

[1,2,3]%

Ta-da!

You should be able to run all this code on LTS-7.16.

What did we learn

(1) Servant and Haskell are fun.

(2) The typeclass machinery of Servant allows for a kind of plug-and-play when it comes to the types you specify in your API. We can take out ReqBody and replace it with our own; on a project I did at work we even replaced the Servant verbs (GET, POST, ...) with our own. We wrote new content types and we even did something similar with ReqBody like you saw here.

(3) It is the remarkable ability of the GHC compiler that we can destructure types during compile-time to influence runtime behavior in a safe and logically sound way. That we can express a tree of API routes at the type-level and then walk over them using typeclass instances, accumulating a server type using type families, is a wonderfully elegant way to build a well-typed web service.

like image 153
hao Avatar answered Oct 19 '22 03:10

hao