json-api-0.1.0.4: Utilities for generating JSON-API payloads

Safe HaskellNone
LanguageHaskell2010

Network.JSONApi.Document

Description

Entry-point module for this package.

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

Synopsis

Documentation

data Document a b c 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 

Fields

Instances

(Eq a, Eq b, Eq c) => Eq (Document a b c) Source # 

Methods

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

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

(Show a, Show b, Show c) => Show (Document a b c) Source # 

Methods

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

show :: Document a b c -> String #

showList :: [Document a b c] -> ShowS #

Generic (Document a b c) Source # 

Associated Types

type Rep (Document a b c) :: * -> * #

Methods

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

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

(ToJSON a, ToJSON b, ToJSON c) => ToJSON (Document a b c) Source # 

Methods

toJSON :: Document a b c -> Value #

toEncoding :: Document a b c -> Encoding #

(FromJSON a, FromJSON b, FromJSON c) => FromJSON (Document a b c) Source # 

Methods

parseJSON :: Value -> Parser (Document a b c) #

type Rep (Document a b c) Source # 
type Rep (Document a b c) = D1 (MetaData "Document" "Network.JSONApi.Document" "json-api-0.1.0.4-XQJNxt8UE1JTVw5IChpYb" False) (C1 (MetaCons "Document" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_data") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ResourceData a b))) ((:*:) (S1 (MetaSel (Just Symbol "_links") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Links))) (S1 (MetaSel (Just Symbol "_meta") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Meta c)))))))

data ErrorDocument a b 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

Constructors

ErrorDocument 

Instances

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

Methods

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

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

(Show a, Show b) => Show (ErrorDocument a b) Source # 
Generic (ErrorDocument a b) Source # 

Associated Types

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

Methods

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

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

(ToJSON a, ToJSON b) => ToJSON (ErrorDocument a b) Source # 
(FromJSON a, FromJSON b) => FromJSON (ErrorDocument a b) Source # 

Methods

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

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

data Error a Source #

Type for providing application-specific detail to unsuccessful API responses.

Specification: http://jsonapi.org/format/#error-objects

Constructors

Error 

Instances

Eq a => Eq (Error a) Source # 

Methods

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

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

Show a => Show (Error a) Source # 

Methods

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

show :: Error a -> String #

showList :: [Error a] -> ShowS #

Generic (Error a) Source # 

Associated Types

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

Methods

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

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

ToJSON a => ToJSON (Error a) Source # 

Methods

toJSON :: Error a -> Value #

toEncoding :: Error a -> Encoding #

FromJSON a => FromJSON (Error a) Source # 

Methods

parseJSON :: Value -> Parser (Error a) #

Default (Error a) Source # 

Methods

def :: Error a #

type Rep (Error a) Source # 

data ResourceData a b 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 b) 
List [Resource a b] 

Instances

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

Methods

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

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

(Show a, Show b) => Show (ResourceData a b) Source # 
Generic (ResourceData a b) Source # 

Associated Types

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

Methods

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

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

(ToJSON a, ToJSON b) => ToJSON (ResourceData a b) Source # 
(FromJSON a, FromJSON b) => FromJSON (ResourceData a b) Source # 

Methods

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

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

data Relationship Source #

A type representing the Relationship between 2 entities

A Relationship provides basic information for fetching further information about a related resource.

Specification: http://jsonapi.org/format/#document-resource-object-relationships

data Resource a b Source #

Type representing a JSON-API resource object.

A Resource supplies standardized data and metadata about a resource.

Specification: http://jsonapi.org/format/#document-resource-objects

Instances

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

Methods

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

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

(Show a, Show b) => Show (Resource a b) Source # 

Methods

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

show :: Resource a b -> String #

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

Generic (Resource a b) Source # 

Associated Types

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

Methods

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

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

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

Methods

toJSON :: Resource a b -> Value #

toEncoding :: Resource a b -> Encoding #

(FromJSON a, FromJSON b) => FromJSON (Resource a b) Source # 

Methods

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

type Rep (Resource a b) Source # 

data Identifier Source #

Identifiers are used to encapsulate the minimum amount of information to uniquely identify a resource.

This object will be found at multiple levels of the JSON-API structure

Specification: http://jsonapi.org/format/#document-resource-identifier-objects

Constructors

Identifier 

Fields

data Links Source #

Type representing a JSON-API link object.

Links are an abstraction around an underlying Map consisting of relevance identifiers as keys and URIs as values.

Example JSON: "links": { "self": "http://example.com/posts/1" }

Specification: http://jsonapi.org/format/#document-links

data Meta a Source #

Type representing a JSON-API meta object.

Meta is an abstraction around an underlying Map consisting of resource-specific metadata.

Example JSON: "meta": { "copyright": "Copyright 2015 Example Corp.", "authors": [ "Andre Dawson", "Kirby Puckett", "Don Mattingly", "Ozzie Guillen" ] }

Specification: http://jsonapi.org/format/#document-meta

Constructors

Meta (Map Text a) 

Instances

Eq a => Eq (Meta a) Source # 

Methods

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

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

Ord a => Ord (Meta a) Source # 

Methods

compare :: Meta a -> Meta a -> Ordering #

(<) :: Meta a -> Meta a -> Bool #

(<=) :: Meta a -> Meta a -> Bool #

(>) :: Meta a -> Meta a -> Bool #

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

max :: Meta a -> Meta a -> Meta a #

min :: Meta a -> Meta a -> Meta a #

Show a => Show (Meta a) Source # 

Methods

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

show :: Meta a -> String #

showList :: [Meta a] -> ShowS #

Generic (Meta a) Source # 

Associated Types

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

Methods

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

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

ToJSON a => ToJSON (Meta a) Source # 

Methods

toJSON :: Meta a -> Value #

toEncoding :: Meta a -> Encoding #

FromJSON a => FromJSON (Meta a) Source # 

Methods

parseJSON :: Value -> Parser (Meta a) #

type Rep (Meta a) Source # 
type Rep (Meta a) = D1 (MetaData "Meta" "Network.JSONApi.Meta" "json-api-0.1.0.4-XQJNxt8UE1JTVw5IChpYb" False) (C1 (MetaCons "Meta" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Text a))))

toLinks :: [(Rel, URL)] -> Links Source #

Constructor function for building Links

mkRelationship :: Maybe Identifier -> Maybe Links -> Maybe Relationship Source #

Constructor function for creating a Relationship record

A relationship must contain either an Identifier or a Links record