envelope-0.2.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 a, Eq e) => Eq (Envelope' e a) Source # 

Methods

(==) :: Envelope' e a -> Envelope' e a -> Bool #

(/=) :: Envelope' e a -> Envelope' e a -> Bool #

(Data a, Data e) => Data (Envelope' e a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Envelope' e a -> c (Envelope' e a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Envelope' e a) #

toConstr :: Envelope' e a -> Constr #

dataTypeOf :: Envelope' e a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Envelope' e a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d b. (Data d, Data b) => c (t d b)) -> Maybe (c (Envelope' e a)) #

gmapT :: (forall b. Data b => b -> b) -> Envelope' e a -> Envelope' e a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Envelope' e a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Envelope' e a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Envelope' e a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Envelope' e a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Envelope' e a -> m (Envelope' e a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Envelope' e a -> m (Envelope' e a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Envelope' e a -> m (Envelope' e a) #

(Show a, Show e) => Show (Envelope' e a) Source # 

Methods

showsPrec :: Int -> Envelope' e a -> ShowS #

show :: Envelope' e a -> String #

showList :: [Envelope' e a] -> ShowS #

Generic (Envelope' e a) Source # 

Associated Types

type Rep (Envelope' e a) :: * -> * #

Methods

from :: Envelope' e a -> Rep (Envelope' e a) x #

to :: Rep (Envelope' e a) x -> Envelope' e a #

(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.

(ToForm a, ToForm e) => ToForm (Envelope' e a) Source #

Uses the underlying ToForm instance for both the EnvelopeErr case and the EnvelopeSuccess case.

Methods

toForm :: Envelope' e a -> Form #

(FromForm a, FromHttpApiData e) => FromForm (Envelope' (Err e) a) Source #

Looks for the key "error" in the Form. If it is found, assume this form is an 'Err e'. If it is not found, assume this Form is an a.

WARNING: If the a is encoded with a key "error", this Form will be decoded as a EnvelopeErr instead of a EnvelopeSuccess. This is probably not what you want.

Methods

fromForm :: Form -> Either Text (Envelope' (Err e) a) #

type Rep (Envelope' e a) Source # 
type Rep (Envelope' e a) = D1 (MetaData "Envelope'" "Web.Envelope" "envelope-0.2.0.0-Dg0lQGg3xVXI3yZhFb57oc" False) ((:+:) (C1 (MetaCons "EnvelopeErr" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 e))) (C1 (MetaCons "EnvelopeSuccess" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a))))

newtype Success a Source #

Newtype wrapper to be able to provide specific instances. Used with Envelope.

Constructors

Success a 

Instances

Eq a => Eq (Success a) Source # 

Methods

(==) :: Success a -> Success a -> Bool #

(/=) :: Success a -> Success a -> Bool #

Data a => Data (Success a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Success a -> c (Success a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Success a) #

toConstr :: Success a -> Constr #

dataTypeOf :: Success a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Success a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Success a)) #

gmapT :: (forall b. Data b => b -> b) -> Success a -> Success a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Success a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Success a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Success a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Success a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Success a -> m (Success a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Success a -> m (Success a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Success a -> m (Success a) #

Show a => Show (Success a) Source # 

Methods

showsPrec :: Int -> Success a -> ShowS #

show :: Success a -> String #

showList :: [Success a] -> ShowS #

Generic (Success a) Source # 

Associated Types

type Rep (Success a) :: * -> * #

Methods

from :: Success a -> Rep (Success a) x #

to :: Rep (Success a) x -> Success a #

ToJSON a => ToJSON (Success a) Source #

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

The resulting JSON object will look like this:

 { "data": ... }
FromJSON e => FromJSON (Success e) Source #

Parse the JSON object produced by the ToJSON instance.

ToForm a => ToForm (Success a) Source #

Use the ToForm instance of the underlying datatype.

Methods

toForm :: Success a -> Form #

FromForm a => FromForm (Success a) Source #

Use the FromForm instance of the underlying datatype.

Methods

fromForm :: Form -> Either Text (Success a) #

type Rep (Success a) Source # 
type Rep (Success a) = D1 (MetaData "Success" "Web.Envelope" "envelope-0.2.0.0-Dg0lQGg3xVXI3yZhFb57oc" True) (C1 (MetaCons "Success" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

data Err e Source #

Wrapper to add an extra field with info about the error. Used with Envelope.

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 # 

Methods

(==) :: Err e -> Err e -> Bool #

(/=) :: Err e -> Err e -> Bool #

Data e => Data (Err e) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Err e -> c (Err e) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Err e) #

toConstr :: Err e -> Constr #

dataTypeOf :: Err e -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Err e)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d a. (Data d, Data a) => c (t d a)) -> Maybe (c (Err e)) #

gmapT :: (forall b. Data b => b -> b) -> Err e -> Err e #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Err e -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Err e -> r #

gmapQ :: (forall d. Data d => d -> u) -> Err e -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Err e -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Err e -> m (Err e) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Err e -> m (Err e) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Err e -> m (Err e) #

Show e => Show (Err e) Source # 

Methods

showsPrec :: Int -> Err e -> ShowS #

show :: Err e -> String #

showList :: [Err e] -> ShowS #

Generic (Err e) Source # 

Associated Types

type Rep (Err e) :: * -> * #

Methods

from :: Err e -> Rep (Err e) x #

to :: Rep (Err e) x -> Err e #

ToJSON e => ToJSON (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": .... }

Methods

toJSON :: Err e -> Value #

toEncoding :: Err e -> Encoding #

toJSONList :: [Err e] -> Value #

toEncodingList :: [Err e] -> Encoding #

FromJSON e => FromJSON (Err e) Source #

Parse the JSON object produced by the ToJSON instance.

Methods

parseJSON :: Value -> Parser (Err e) #

parseJSONList :: Value -> Parser [Err e] #

ToHttpApiData e => ToForm (Err e) Source #

Just use the ToForm instance of the underlying datatype.

The resulting Form object will look like this:

 [("extra", ...), ("error", ....)]

Methods

toForm :: Err e -> Form #

FromHttpApiData e => FromForm (Err e) Source #

Parse a form produced by the ToForm instance. Use FromHttpApiDatas parseQueryParam to parse the error parameter.

Methods

fromForm :: Form -> Either Text (Err e) #

(FromForm a, FromHttpApiData e) => FromForm (Envelope' (Err e) a) Source #

Looks for the key "error" in the Form. If it is found, assume this form is an 'Err e'. If it is not found, assume this Form is an a.

WARNING: If the a is encoded with a key "error", this Form will be decoded as a EnvelopeErr instead of a EnvelopeSuccess. This is probably not what you want.

Methods

fromForm :: Form -> Either Text (Envelope' (Err e) a) #

type Rep (Err e) Source # 
type Rep (Err e) = D1 (MetaData "Err" "Web.Envelope" "envelope-0.2.0.0-Dg0lQGg3xVXI3yZhFb57oc" False) (C1 (MetaCons "Err" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "errErr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 e)) (S1 (MetaSel (Just Symbol "errExtra") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)))))

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"})