| Copyright | (c) Dennis Gosnell 2016 |
|---|---|
| License | BSD-style (see LICENSE file) |
| Maintainer | cdep.illabout@gmail.com |
| Stability | experimental |
| Portability | POSIX |
| Safe Haskell | None |
| Language | Haskell2010 |
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.
- type Envelope e a = Envelope' (Err e) (Success a)
- data Envelope' e a
- = EnvelopeErr e
- | EnvelopeSuccess a
- newtype Success a = Success a
- data Err e = Err {}
- toErr :: e -> Text -> Err e
- toErr' :: e -> Err e
- throwEnvelopeErr :: MonadError (Err e) m => e -> Text -> m a
- throwEnvelopeErr' :: MonadError (Err e) m => e -> m a
- toSuccessEnvelope :: a -> Envelope e a
- toErrEnvelope :: e -> Text -> Envelope e a
- toErrEnvelope' :: e -> Envelope e a
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'.
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 # | |
| (Data a, Data e) => Data (Envelope' e a) Source # | |
| (Show a, Show e) => 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 If that fails, try to parse an error response. If you are using the
|
| (ToForm a, ToForm e) => ToForm (Envelope' e a) Source # | Uses the underlying |
| (FromForm a, FromHttpApiData e) => FromForm (Envelope' (Err e) a) Source # | Looks for the key WARNING: If the |
| type Rep (Envelope' e a) Source # | |
Newtype wrapper to be able to provide specific 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 # | For The resulting JSON object will look like this: { "data": ... }
|
| FromJSON e => FromJSON (Success e) Source # | Parse the JSON object produced by the |
| ToForm a => ToForm (Success a) Source # | Use the |
| FromForm a => FromForm (Success a) Source # | Use the |
| type Rep (Success a) Source # | |
Wrapper to add an extra field with info about the error. Used with
Envelope.
Constructors
| Err | |
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 # | For The resulting JSON object will look like this: { "extra": ..., "error": .... }
|
| FromJSON e => FromJSON (Err e) Source # | Parse the JSON object produced by the |
| ToHttpApiData e => ToForm (Err e) Source # | Just use the The resulting Form object will look like this: [("extra", ...), ("error", ....)]
|
| FromHttpApiData e => FromForm (Err e) Source # | Parse a form produced by the |
| (FromForm a, FromHttpApiData e) => FromForm (Envelope' (Err e) a) Source # | Looks for the key WARNING: If the |
| type Rep (Err e) Source # | |
toErr :: e -> Text -> Err e Source #
Smart constructor for Err.
>>>toErr "DB_ERROR" "an error occurred"Err {errErr = "DB_ERROR", errExtra = Just "an error occurred"}
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 somewhere inside your monad transformer
stacks, this function can be used to throw an error (return early) in a
function.ExceptT (Err e)
>>>import Control.Monad.Except (runExcept)>>>throwEnvelopeErr "BAD_ERROR" "a very bad error occurred!" :: Either (Err String) IntLeft (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) IntLeft (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 IntEnvelopeSuccess (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 IntEnvelopeErr (Err {errErr = "DB_ERROR", errExtra = Just "there was an error with the database"})
toErrEnvelope' :: e -> Envelope e a Source #
Wrap an a in an error Envelope.
>>>toErrEnvelope' "DB_ERROR" :: Envelope String IntEnvelopeErr (Err {errErr = "DB_ERROR", errExtra = Nothing})