json-api-lib-0.3.0.0: Utilities for generating JSON-API payloads

Safe HaskellNone
LanguageHaskell2010

Network.JSONApi.Document

Description

Contains representations of the top-level JSON-API document structure.

Synopsis

Documentation

data Document a Source #

The Document type represents the top-level JSON-API requirement.

data attribute - the resulting JSON may be either a singleton resource or a list of resources. See Resource for the construction.

For more information see: http://jsonapi.org/format/#document-top-level

Constructors

Document 
Instances
Eq a => Eq (Document a) Source # 
Instance details

Defined in Network.JSONApi.Document

Methods

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

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

Show a => Show (Document a) Source # 
Instance details

Defined in Network.JSONApi.Document

Methods

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

show :: Document a -> String #

showList :: [Document a] -> ShowS #

Generic (Document a) Source # 
Instance details

Defined in Network.JSONApi.Document

Associated Types

type Rep (Document a) :: Type -> Type #

Methods

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

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

ToJSON a => ToJSON (Document a) Source # 
Instance details

Defined in Network.JSONApi.Document

FromJSON a => FromJSON (Document a) Source # 
Instance details

Defined in Network.JSONApi.Document

NFData a => NFData (Document a) Source # 
Instance details

Defined in Network.JSONApi.Document

Methods

rnf :: Document a -> () #

type Rep (Document a) Source # 
Instance details

Defined in Network.JSONApi.Document

data ResourceData a Source #

The Resource type encapsulates the underlying Resource

Included in the top-level Document, the Resource may be either a singleton resource or a list.

For more information see: http://jsonapi.org/format/#document-top-level

Constructors

Singleton (Resource a) 
List [Resource a] 
Instances
Eq a => Eq (ResourceData a) Source # 
Instance details

Defined in Network.JSONApi.Document

Show a => Show (ResourceData a) Source # 
Instance details

Defined in Network.JSONApi.Document

Generic (ResourceData a) Source # 
Instance details

Defined in Network.JSONApi.Document

Associated Types

type Rep (ResourceData a) :: Type -> Type #

Methods

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

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

ToJSON a => ToJSON (ResourceData a) Source # 
Instance details

Defined in Network.JSONApi.Document

FromJSON a => FromJSON (ResourceData a) Source # 
Instance details

Defined in Network.JSONApi.Document

NFData a => NFData (ResourceData a) Source # 
Instance details

Defined in Network.JSONApi.Document

Methods

rnf :: ResourceData a -> () #

type Rep (ResourceData a) Source # 
Instance details

Defined in Network.JSONApi.Document

type Rep (ResourceData a) = D1 (MetaData "ResourceData" "Network.JSONApi.Document" "json-api-lib-0.3.0.0-EA1mdVZ1o5NJWsxzWCLCdF" False) (C1 (MetaCons "Singleton" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Resource a))) :+: C1 (MetaCons "List" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Resource a])))

data ErrorDocument a Source #

The ErrorDocument type represents the alternative form of the top-level JSON-API requirement.

error attribute - a descriptive object encapsulating application-specific error detail.

For more information see: http://jsonapi.org/format/#errors

Instances
Eq (ErrorDocument a) Source # 
Instance details

Defined in Network.JSONApi.Document

Show (ErrorDocument a) Source # 
Instance details

Defined in Network.JSONApi.Document

Generic (ErrorDocument a) Source # 
Instance details

Defined in Network.JSONApi.Document

Associated Types

type Rep (ErrorDocument a) :: Type -> Type #

ToJSON a => ToJSON (ErrorDocument a) Source # 
Instance details

Defined in Network.JSONApi.Document

FromJSON a => FromJSON (ErrorDocument a) Source # 
Instance details

Defined in Network.JSONApi.Document

NFData a => NFData (ErrorDocument a) Source # 
Instance details

Defined in Network.JSONApi.Document

Methods

rnf :: ErrorDocument a -> () #

type Rep (ErrorDocument a) Source # 
Instance details

Defined in Network.JSONApi.Document

type Rep (ErrorDocument a) = D1 (MetaData "ErrorDocument" "Network.JSONApi.Document" "json-api-lib-0.3.0.0-EA1mdVZ1o5NJWsxzWCLCdF" False) (C1 (MetaCons "ErrorDocument" PrefixI True) (S1 (MetaSel (Just "_error") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Error a)) :*: (S1 (MetaSel (Just "_errorLinks") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Links)) :*: S1 (MetaSel (Just "_errorMeta") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Meta)))))

data Included Source #

The Included type is an abstraction used to constrain the included section of the Document to JSON serializable Resource objects while enabling a heterogeneous list of Resource types.

No data constructors for this type are exported as we need to constrain the Value to a heterogeneous list of Resource types. See mkIncludedResource for creating Included types.

Instances
Show Included Source # 
Instance details

Defined in Network.JSONApi.Document

Generic Included Source # 
Instance details

Defined in Network.JSONApi.Document

Associated Types

type Rep Included :: Type -> Type #

Methods

from :: Included -> Rep Included x #

to :: Rep Included x -> Included #

NFData Included Source # 
Instance details

Defined in Network.JSONApi.Document

Methods

rnf :: Included -> () #

type Rep Included Source # 
Instance details

Defined in Network.JSONApi.Document

type Rep Included = D1 (MetaData "Included" "Network.JSONApi.Document" "json-api-lib-0.3.0.0-EA1mdVZ1o5NJWsxzWCLCdF" True) (C1 (MetaCons "Included" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Value])))

mkDocument :: ResourcefulEntity a => a -> Maybe Links -> Maybe Meta -> Document a Source #

Constructor function for the Document data type which takes a single ResourcefulEntity.

See mkCompoundDocument for constructing compound Document including 'side-loaded' resources

mkDocuments :: ResourcefulEntity a => [a] -> Maybe Links -> Maybe Meta -> Document a Source #

Constructor function for the Document data type which takes a list of Resourceful entities.

See mkCompoundDocument for constructing compound Document including 'side-loaded' resources

mkSimpleDocument :: ResourcefulEntity a => a -> Document a Source #

A function for a single resourceful entity and document which do not require links or Meta data.

mkSimpleDocuments :: ResourcefulEntity a => [a] -> Document a Source #

A function for a multiple resourceful entities and document which do not require links or Meta data.

mkSimpleDocument' :: ResourceData a -> Document a Source #

A function for document which do not require links or Meta data.

mkCompoundDocument :: ResourcefulEntity a => a -> Maybe Links -> Maybe Meta -> Included -> Document a Source #

Constructor function for the Document data type. See mkIncludedResource for constructing the Included type.

Supports building compound documents http://jsonapi.org/format/#document-compound-documents

mkCompoundDocuments :: ResourcefulEntity a => [a] -> Maybe Links -> Maybe Meta -> Included -> Document a Source #

Constructor function for the Document data type. See mkIncludedResource for constructing the Included type.

Supports building compound documents http://jsonapi.org/format/#document-compound-documents

mkIncludedResource :: (ResourcefulEntity a, ToJSON a) => a -> Included Source #

Constructor function for the Document data type.

Supports building compound documents http://jsonapi.org/format/#document-compound-documents