aeson-injector-1.0.3.0: Injecting fields into aeson values

Copyright(c) Anton Gushcha 2016
LicenseMIT
Maintainerncrashed@gmail.com
Stabilityexperimental
PortabilityPortable
Safe HaskellNone
LanguageHaskell2010

Data.Aeson.WithField

Contents

Description

When builds a RESTful API one often faces the problem that some methods need inbound data without unique identifier (for instance, a creation of new resource) and some methods need the same outbound data with additional fields attached to the response.

The module provides you with WithField and WithFields data types that help you to solve the issue without code duplication.

It is small utility library that is intented to be used in RESTful APIs, especially with servant and Swagger. Its main purpose is simple injection of fields into JSONs produced by aeson library.

Consider the following common data type in web service developing:

data News = News {
  title :: Text
, body :: Text
, author :: Text
, timestamp :: UTCTime  
}

-- Consider we have simple ToJSON and FromJSON instances
$(deriveJSON defaultOptions ''News) 

ToJSON instance produces JSON's like:

{
  "title": "Awesome piece of news!"
, "body": "Big chunk of text"
, "author": "Just Me"
, "timestamp": "2016-07-26T18:54:42.678999Z"
}

Now one can create a simple web server with servant DSL:

type NewsId = Word 

type NewsAPI = 
       ReqBody '[JSON] News :> Post '[JSON] NewsId
  :<|> Capture "news-id" NewsId :> Get '[JSON] News
  :<|> "list" :> Get '[JSON] [News]

All seems legit, but, wait a second, an API user definitely would like to know id of news in the "list" method. One way to do this is declare new data type NewsInfo with additional field, but it is bad solution as requires to code duplication for each resource.

So, here aeson-injector steps in, now you can write:

type NewsAPI = 
       ReqBody '[JSON] News :> Post '[JSON] NewsId
  :<|> Capture "news-id" NewsId :> Get '[JSON] News
  :<|> "list" :> Get '[JSON] [WithField "id" NewsId News]

WithField "id" NewsId News or simply WithId NewsId News wraps you data type and injects "id" field in produced JSON values:

>>> encode (WithField 42 myNews :: WithField "id" NewsId News)
{
  "id": 42
, "title": "Awesome piece of news!"
, "body": "Big chunk of text"
, "author": "Just Me"
, "timestamp": "2016-07-26T18:54:42.678999Z"
}

WithField data type has FromJSON instance for seamless parsing of data with injected fields and ToSchema instance for servant-swagger support.

Injecting multiple values

The library also has more general data type 'WithFields a b' that injects fields of 'toJSON a' into 'toJSON b'.

 haskell
data NewsPatch = NewsPatch {
  taggs :: [Text]
, rating :: Double
}
$(deriveJSON defaultOptions ''NewsPatch) 
 haskell
let myNewsPatch = NewsPatch ["tag1", "tag2"] 42 
in encode $ WithFields myNewsPatch myNews
{
  "title": "Awesome piece of news!"
, "body": "Big chunk of text"
, "author": "Just Me"
, "timestamp": "2016-07-26T18:54:42.678999Z"
, "tags": ["tag1", "tag2"]
, "rating": 42.0
}

Corner cases

Unfortunately, we cannot inject in non object values of produced JSON, so the library creates a wrapper object around non-object value:

encode (WithId 0 "non-object" :: WithId Int String)
{
  "id": 0 
, "value": "non-object"
}

The same story is about WithFields data type:

encode (WithFields 0 "non-object" :: WithFields Int String)
{
  "injected": 0 
, "value": "non-object"
}

Synopsis

Single field injector

data WithField s a b Source #

Injects field a into b with tag s. It has special instances for ToJSON and FromJSON for such injection and corresponding Swagger ToSchema instance.

For instance:

>>> encode (WithField "val" (Left 42) :: WithField "injected" String (Either Int Int))
"{\"Left\":42,\"id\":\"val\"}"

If the instance cannot inject field (in case of single values and arrays), it wraps the result in the following way:

>>> encode (WithField "val" 42 :: WithField "injected" String Int)
"{\"value\":42,\"injected\":\"val\"}"

Constructors

WithField !a !b 

Instances

Bifunctor (WithField s) Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> WithField s a c -> WithField s b d #

first :: (a -> b) -> WithField s a c -> WithField s b c #

second :: (b -> c) -> WithField s a b -> WithField s a c #

Functor (WithField s a) Source # 

Methods

fmap :: (a -> b) -> WithField s a a -> WithField s a b #

(<$) :: a -> WithField s a b -> WithField s a a #

(Eq b, Eq a) => Eq (WithField s a b) Source # 

Methods

(==) :: WithField s a b -> WithField s a b -> Bool #

(/=) :: WithField s a b -> WithField s a b -> Bool #

(Read b, Read a) => Read (WithField s a b) Source # 
(Show b, Show a) => Show (WithField s a b) Source # 

Methods

showsPrec :: Int -> WithField s a b -> ShowS #

show :: WithField s a b -> String #

showList :: [WithField s a b] -> ShowS #

Generic (WithField s a b) Source # 

Associated Types

type Rep (WithField s a b) :: * -> * #

Methods

from :: WithField s a b -> Rep (WithField s a b) x #

to :: Rep (WithField s a b) x -> WithField s a b #

(KnownSymbol s, ToJSON a, ToJSON b) => ToJSON (WithField s a b) Source #

Note: the instance injects field only in Object case. In other cases it forms a wrapper around the Value produced by toJSON of inner b body.

Example of wrapper:

{ "id": 0, "value": [1, 2, 3] }

Methods

toJSON :: WithField s a b -> Value #

toEncoding :: WithField s a b -> Encoding #

(KnownSymbol s, FromJSON a, FromJSON b) => FromJSON (WithField s a b) Source #

Note: the instance tries to parse the json as object with additional field value, if it fails it assumes that it is a wrapper produced by corresponding ToJSON instance.

Methods

parseJSON :: Value -> Parser (WithField s a b) #

(NFData a, NFData b) => NFData (WithField s a b) Source # 

Methods

rnf :: WithField s a b -> () #

(ToSample a, ToSample b) => ToSample (WithField s a b) Source # 

Methods

toSamples :: Proxy * (WithField s a b) -> [(Text, WithField s a b)] #

(KnownSymbol s, ToSchema a, ToSchema b) => ToSchema (WithField s a b) Source #

Note: the instance tries to generate schema of the json as object with additional field value, if it fails it assumes that it is a wrapper produced by corresponding ToJSON instance.

type Rep (WithField s a b) Source # 
type Rep (WithField s a b) = D1 (MetaData "WithField" "Data.Aeson.WithField" "aeson-injector-1.0.3.0-I5cAExstMUeF24jItoCBET" False) (C1 (MetaCons "WithField" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 b))))

type WithId i a = WithField "id" i a Source #

Workaround for a problem that is discribed as: sometimes I need a id with the data, sometimes not.

The important note that ToJSON and FromJSON instances behaves as it is a but with additional id field.

Multiple fields injector

data WithFields a b Source #

Merge fields of a into b, more general version of WithField.

The usual mode of the data type assumes that ToJSON instances of a and b produce Object subtype of aeson Value. If it is not true, a wrapper layer is introduced.

If a is not a Object, the wrapper contains injected field with body of a. If b is not a Object, the wrapper contains value field with body of b. If both are not Object, the wrapper contains injected and value keys with a and b respectively.

Constructors

WithFields !a !b 

Instances

Bifunctor WithFields Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> WithFields a c -> WithFields b d #

first :: (a -> b) -> WithFields a c -> WithFields b c #

second :: (b -> c) -> WithFields a b -> WithFields a c #

Functor (WithFields a) Source # 

Methods

fmap :: (a -> b) -> WithFields a a -> WithFields a b #

(<$) :: a -> WithFields a b -> WithFields a a #

(Eq b, Eq a) => Eq (WithFields a b) Source # 

Methods

(==) :: WithFields a b -> WithFields a b -> Bool #

(/=) :: WithFields a b -> WithFields a b -> Bool #

(Read b, Read a) => Read (WithFields a b) Source # 
(Show b, Show a) => Show (WithFields a b) Source # 

Methods

showsPrec :: Int -> WithFields a b -> ShowS #

show :: WithFields a b -> String #

showList :: [WithFields a b] -> ShowS #

Generic (WithFields a b) Source # 

Associated Types

type Rep (WithFields a b) :: * -> * #

Methods

from :: WithFields a b -> Rep (WithFields a b) x #

to :: Rep (WithFields a b) x -> WithFields a b #

(ToJSON a, ToJSON b) => ToJSON (WithFields a b) Source #

Note: the instance injects field only in Object case. In other cases it forms a wrapper around the Value produced by toJSON of inner b body.

Example of wrapper when b is not a Object, b goes into "value" field:

{ "field1": 0, "field2": "val", "value": [1, 2, 3] }

Example of wrapper when a is not a Object, but b is. a goes into "injected" field:

{ "field1": 0, "field2": "val", "injected": [1, 2, 3] }

Example of wrapper when as a is not a Object, as b is not. a goes into "injected" field, b goes into "value" field:

{ "value": 42, "injected": [1, 2, 3] }
(FromJSON a, FromJSON b) => FromJSON (WithFields a b) Source #

Note: the instance tries to parse the json as object with additional field value, if it fails it assumes that it is a wrapper produced by corresponding ToJSON instance.

Methods

parseJSON :: Value -> Parser (WithFields a b) #

(NFData a, NFData b) => NFData (WithFields a b) Source # 

Methods

rnf :: WithFields a b -> () #

(ToSample a, ToSample b) => ToSample (WithFields a b) Source # 

Methods

toSamples :: Proxy * (WithFields a b) -> [(Text, WithFields a b)] #

(ToSchema a, ToSchema b) => ToSchema (WithFields a b) Source #

Note: the instance tries to generate schema of the json as object with additional field value, if it fails it assumes that it is a wrapper produced by corresponding ToJSON instance.

type Rep (WithFields a b) Source # 
type Rep (WithFields a b) = D1 (MetaData "WithFields" "Data.Aeson.WithField" "aeson-injector-1.0.3.0-I5cAExstMUeF24jItoCBET" False) (C1 (MetaCons "WithFields" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 b))))

Single field wrapper

newtype OnlyField s a Source #

Special case, when you want to wrap your type a in field with name s.

>>> encode (OnlyField 0 :: OnlyField "id" Int)
"{\"id\":0}"
>>> encode $ toSchema (Proxy :: Proxy (OnlyField "id" Int))
"{\"required\":[\"id\"],\"type\":\"object\",\"properties\":{\"id\":{\"maximum\":9223372036854775807,\"minimum\":-9223372036854775808,\"type\":\"integer\"}}}"

Also the type can be used as an endpoint for WithField:

>>> encode (WithField True (OnlyField 0) :: WithField "val" Bool (OnlyField "id" Int))
"{\"id\":0,\"val\":true}"

Constructors

OnlyField 

Fields

Instances

Functor (OnlyField s) Source # 

Methods

fmap :: (a -> b) -> OnlyField s a -> OnlyField s b #

(<$) :: a -> OnlyField s b -> OnlyField s a #

Eq a => Eq (OnlyField s a) Source # 

Methods

(==) :: OnlyField s a -> OnlyField s a -> Bool #

(/=) :: OnlyField s a -> OnlyField s a -> Bool #

Read a => Read (OnlyField s a) Source # 
Show a => Show (OnlyField s a) Source # 

Methods

showsPrec :: Int -> OnlyField s a -> ShowS #

show :: OnlyField s a -> String #

showList :: [OnlyField s a] -> ShowS #

Generic (OnlyField s a) Source # 

Associated Types

type Rep (OnlyField s a) :: * -> * #

Methods

from :: OnlyField s a -> Rep (OnlyField s a) x #

to :: Rep (OnlyField s a) x -> OnlyField s a #

(KnownSymbol s, ToJSON a) => ToJSON (OnlyField s a) Source # 

Methods

toJSON :: OnlyField s a -> Value #

toEncoding :: OnlyField s a -> Encoding #

(KnownSymbol s, FromJSON a) => FromJSON (OnlyField s a) Source # 

Methods

parseJSON :: Value -> Parser (OnlyField s a) #

ToSample a => ToSample (OnlyField s a) Source # 

Methods

toSamples :: Proxy * (OnlyField s a) -> [(Text, OnlyField s a)] #

(KnownSymbol s, ToSchema a) => ToSchema (OnlyField s a) Source # 
type Rep (OnlyField s a) Source # 
type Rep (OnlyField s a) = D1 (MetaData "OnlyField" "Data.Aeson.WithField" "aeson-injector-1.0.3.0-I5cAExstMUeF24jItoCBET" True) (C1 (MetaCons "OnlyField" PrefixI True) (S1 (MetaSel (Just Symbol "unOnlyField") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

type OnlyId i = OnlyField "id" i Source #

Special case for the most common "id" field