Copyright | (c) Anton Gushcha 2016 |
---|---|
License | MIT |
Maintainer | ncrashed@gmail.com |
Stability | experimental |
Portability | Portable |
Safe Haskell | None |
Language | Haskell2010 |
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 simpleToJSON
andFromJSON
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]
or simply WithField
"id" NewsId News
wraps you data type
and injects "id" field in produced JSON values:WithId
NewsId News
>>>
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
- data WithField (s :: Symbol) a b = WithField !a !b
- type WithId i a = WithField "id" i a
- data WithFields a b = WithFields !a !b
- newtype OnlyField (s :: Symbol) a = OnlyField {
- unOnlyField :: a
- type OnlyId i = OnlyField "id" i
Single field injector
data WithField (s :: Symbol) 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\"}"
`WithField s a b` always overwites field s
in JSON produced by b
.
WithField !a !b |
Instances
Bifunctor (WithField s) Source # | |
Functor (WithField s a) Source # | |
(Eq a, Eq b) => Eq (WithField s a b) Source # | |
(Read a, Read b) => Read (WithField s a b) Source # | |
(Show a, Show b) => Show (WithField s a b) Source # | |
Generic (WithField s a b) Source # | |
(KnownSymbol s, ToJSON a, ToJSON b) => ToJSON (WithField s a b) Source # | Note: the instance injects field only in Example of wrapper: { "id": 0, "value": [1, 2, 3] } |
Defined in Data.Aeson.WithField | |
(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 Note: The instance tries to parse the |
(NFData a, NFData b) => NFData (WithField s a b) Source # | |
Defined in Data.Aeson.WithField | |
(ToSample a, ToSample b) => ToSample (WithField s a b) Source # | |
(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 |
Defined in Data.Aeson.WithField declareNamedSchema :: Proxy (WithField s a b) -> Declare (Definitions Schema) NamedSchema # | |
type Rep (WithField s a b) Source # | |
Defined in Data.Aeson.WithField type Rep (WithField s a b) = D1 (MetaData "WithField" "Data.Aeson.WithField" "aeson-injector-1.1.3.0-6MY5WVAvsf2AfVianu6uUb" False) (C1 (MetaCons "WithField" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 b))) |
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 Value
subtype of aeson Value
. If it is not true, a wrapper
layer is introduced.
If a
is not a Value
, the wrapper contains injected
field with body of a
.
If b
is not a Value
, the wrapper contains value
field with body of b
.
If both are not Value
, the wrapper contains injected
and value
keys with
a
and b
respectively.
WithFields !a !b |
Instances
Bifunctor WithFields Source # | |
Defined in Data.Aeson.WithField 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 # | |
Defined in Data.Aeson.WithField fmap :: (a0 -> b) -> WithFields a a0 -> WithFields a b # (<$) :: a0 -> WithFields a b -> WithFields a a0 # | |
(Eq a, Eq b) => Eq (WithFields a b) Source # | |
Defined in Data.Aeson.WithField (==) :: WithFields a b -> WithFields a b -> Bool # (/=) :: WithFields a b -> WithFields a b -> Bool # | |
(Read a, Read b) => Read (WithFields a b) Source # | |
Defined in Data.Aeson.WithField readsPrec :: Int -> ReadS (WithFields a b) # readList :: ReadS [WithFields a b] # readPrec :: ReadPrec (WithFields a b) # readListPrec :: ReadPrec [WithFields a b] # | |
(Show a, Show b) => Show (WithFields a b) Source # | |
Defined in Data.Aeson.WithField showsPrec :: Int -> WithFields a b -> ShowS # show :: WithFields a b -> String # showList :: [WithFields a b] -> ShowS # | |
Generic (WithFields a b) Source # | |
Defined in Data.Aeson.WithField type Rep (WithFields a b) :: Type -> Type # 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 Example of wrapper when { "field1": 0, "field2": "val", "value": [1, 2, 3] } Example of wrapper when { "field1": 0, "field2": "val", "injected": [1, 2, 3] } Example of wrapper when as { "value": 42, "injected": [1, 2, 3] } `WithFields a b` always overwites fields in JSON produced by |
Defined in Data.Aeson.WithField toJSON :: WithFields a b -> Value # toEncoding :: WithFields a b -> Encoding # toJSONList :: [WithFields a b] -> Value # toEncodingList :: [WithFields a b] -> Encoding # | |
(ToJSON a, 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 Note: The instance tries to parse the The implementation requires `ToJSON a` to catch fields of |
Defined in Data.Aeson.WithField parseJSON :: Value -> Parser (WithFields a b) # parseJSONList :: Value -> Parser [WithFields a b] # | |
(NFData a, NFData b) => NFData (WithFields a b) Source # | |
Defined in Data.Aeson.WithField rnf :: WithFields a b -> () # | |
(ToSample a, ToSample b) => ToSample (WithFields a b) Source # | |
Defined in Data.Aeson.WithField 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 |
Defined in Data.Aeson.WithField declareNamedSchema :: Proxy (WithFields a b) -> Declare (Definitions Schema) NamedSchema # | |
type Rep (WithFields a b) Source # | |
Defined in Data.Aeson.WithField type Rep (WithFields a b) = D1 (MetaData "WithFields" "Data.Aeson.WithField" "aeson-injector-1.1.3.0-6MY5WVAvsf2AfVianu6uUb" False) (C1 (MetaCons "WithFields" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 b))) |
Single field wrapper
newtype OnlyField (s :: Symbol) 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}"
OnlyField | |
|
Instances
Functor (OnlyField s) Source # | |
Eq a => Eq (OnlyField s a) Source # | |
Read a => Read (OnlyField s a) Source # | |
Show a => Show (OnlyField s a) Source # | |
Generic (OnlyField s a) Source # | |
(KnownSymbol s, ToJSON a) => ToJSON (OnlyField s a) Source # | |
Defined in Data.Aeson.WithField | |
(KnownSymbol s, FromJSON a) => FromJSON (OnlyField s a) Source # | |
ToSample a => ToSample (OnlyField s a) Source # | |
(KnownSymbol s, ToSchema a) => ToSchema (OnlyField s a) Source # | |
Defined in Data.Aeson.WithField declareNamedSchema :: Proxy (OnlyField s a) -> Declare (Definitions Schema) NamedSchema # | |
type Rep (OnlyField s a) Source # | |
Defined in Data.Aeson.WithField |