envelope-0.1.0.0: Defines generic 'Envelope' type to wrap reponses from a JSON API.

Copyright(c) Dennis Gosnell, 2016
LicenseBSD-style (see LICENSE file)
Maintainercdep.illabout@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Web.Envelope

Description

This module contains the Envelope type and helper functions. The Envelope type can be used to wrap responses from a JSON API.

The following is an example of using this package.

First, we will import some needed modules.

>>> import qualified Data.ByteString.Lazy.Char8 as C8
>>> import Data.Aeson (decode, encode)

Let's look at how a success reponse is encoded and decoded. It is encoded as an object with a single member: "data".

>>> let successEnvelope = toSuccessEnvelope 3 :: Envelope Text Int
>>> C8.putStrLn $ encode successEnvelope
{"data":3}
>>> decode "{\"data\":3}" :: Maybe (Envelope Text Int)
Just (EnvelopeSuccess (Success 3))

Now lets look at how an error response is encoded and decoded. It is encoded as an object with two members: "extra" and "error".

>>> let errorEnvelope = toErrEnvelope "DB_ERROR" "there was an error with the database" :: Envelope String Int
>>> C8.putStrLn $ encode errorEnvelope
{"extra":"there was an error with the database","error":"DB_ERROR"}
>>> decode "{\"extra\":\"there was an error with the database\",\"error\":\"DB_ERROR\"}" :: Maybe (Envelope String Int)
Just (EnvelopeErr (Err {errErr = "DB_ERROR", errExtra = Just "there was an error with the database"}))

The Success and Err types are used within the Envelope type synonym.

Synopsis

Documentation

type Envelope e a = Envelope' (Err e) (Success a) Source

Main type to be used. Wrapper around responses from an API, mainly used with a JSON API.

Type synonym around Envelope'.

data Envelope' e a Source

Wrapper around either a success or an error. Isomorphic to Either.

The only interesting part of this type is the ToJSON and FromJSON instances.

Constructors

EnvelopeErr e 
EnvelopeSuccess a 

Instances

(Eq e, Eq a) => Eq (Envelope' e a) Source 
(Data e, Data a) => Data (Envelope' e a) Source 
(Show e, Show a) => Show (Envelope' e a) Source 
Generic (Envelope' e a) Source 
(ToJSON e, ToJSON a) => ToJSON (Envelope' e a) Source 
(FromJSON e, FromJSON a) => FromJSON (Envelope' e a) Source

Tries to parse a successful response. If you are using the Envelope type synonym, this will use the FromJSON instance for Success.

If that fails, try to parse an error response. If you are using the Envelope type synonym, this will use the FromJSON instance for Err.

type Rep (Envelope' e a) Source 

newtype Success a Source

Newtype wrapper to be able to provide ToJSON and FromJSON instances. Used with Envelope.

Constructors

Success a 

Instances

Eq a => Eq (Success a) Source 
Data a => Data (Success a) Source 
Show a => Show (Success a) Source 
Generic (Success a) Source 
ToJSON a => ToJSON (Success a) Source 
FromJSON e => FromJSON (Success e) Source

For Success a, wrap the a in an object with a "data" field.

The resulting JSON object will look like this:

 { "data": ... }
type Rep (Success a) Source 

data Err e Source

Newtype wrapper to be able to provide ToJSON and FromJSON instances.

Constructors

Err 

Fields

errErr :: e

Actual error information we want to send.

errExtra :: Maybe Text

Additional error information in plain text.

Instances

Eq e => Eq (Err e) Source 
Data e => Data (Err e) Source 
Show e => Show (Err e) Source 
Generic (Err e) Source 
ToJSON e => ToJSON (Err e) Source 
FromJSON e => FromJSON (Err e) Source

For Err e, wrap the e in an object with "extra" and "error" fields.

The resulting JSON object will look like this:

 { "extra": ..., "error": .... }
type Rep (Err e) Source 

throwEnvelopeErr :: MonadError (Err e) m => e -> Text -> m a Source

Throw an 'Err e' using throwError in a Monad that implements MonadError.

If you have ExceptT (Err e) somewhere inside your monad transformer stacks, this function can be used to throw an error (return early) in a function.

>>> import Control.Monad.Except (runExcept)
>>> throwEnvelopeErr "BAD_ERROR" "a very bad error occurred!" :: Either (Err String) Int
Left (Err {errErr = "BAD_ERROR", errExtra = Just "a very bad error occurred!"})

Here is a longer example using a monad stack.

type MyMonadStack = ReaderT Int (ExceptT (Err String) IO)

doSomething :: Int -> MyMonadStack Int
doSomething int =
    if int < 0
        then
            throwEnvelopeErr "INT_TOO_SMALL" "the integer passed to doSomething is too small"
        else
            return (int + 1)

throwEnvelopeErr' :: MonadError (Err e) m => e -> m a Source

Like throwEnvelopeErr but without providing a message.

>>> import Control.Monad.Except (runExcept)
>>> throwEnvelopeErr "BAD_ERROR" "a very bad error occurred!" :: Either (Err String) Int
Left (Err {errErr = "BAD_ERROR", errExtra = Just "a very bad error occurred!"})

toSuccessEnvelope :: a -> Envelope e a Source

Wrap an a in a success Envelope.

>>> toSuccessEnvelope 3 :: Envelope String Int
EnvelopeSuccess (Success 3)

toErrEnvelope :: e -> Text -> Envelope e a Source

Wrap an a and an additional message in an error Envelope.

>>> toErrEnvelope "DB_ERROR" "there was an error with the database" :: Envelope String Int
EnvelopeErr (Err {errErr = "DB_ERROR", errExtra = Just "there was an error with the database"})