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

Safe HaskellNone
LanguageHaskell2010

Network.JSONApi

Description

Entry-point module for this package.

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

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

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

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.1.1.0-HA2FSjEkbMOH3K6uHch1q9" 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

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.1.1.0-HA2FSjEkbMOH3K6uHch1q9" 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

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 (Error a) Source # 
Instance details

Defined in Network.JSONApi.Error

Methods

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

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

Show (Error a) Source # 
Instance details

Defined in Network.JSONApi.Error

Methods

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

show :: Error a -> String #

showList :: [Error a] -> ShowS #

Generic (Error a) Source # 
Instance details

Defined in Network.JSONApi.Error

Associated Types

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

Methods

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

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

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

Defined in Network.JSONApi.Error

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

Defined in Network.JSONApi.Error

Default (Error a) Source # 
Instance details

Defined in Network.JSONApi.Error

Methods

def :: Error a #

type Rep (Error a) Source # 
Instance details

Defined in Network.JSONApi.Error

newtype PageNum Source #

Constructors

PageNum 

Fields

Instances
Show PageNum Source # 
Instance details

Defined in Network.JSONApi.Resource

newtype PageSize Source #

We can specify limits on the number of rows we would like back from the database

Constructors

PageSize 

Fields

Instances
Show PageSize Source # 
Instance details

Defined in Network.JSONApi.Resource

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

Instances
Eq Relationship Source # 
Instance details

Defined in Network.JSONApi.Resource

Show Relationship Source # 
Instance details

Defined in Network.JSONApi.Resource

Generic Relationship Source # 
Instance details

Defined in Network.JSONApi.Resource

Associated Types

type Rep Relationship :: Type -> Type #

ToJSON Relationship Source # 
Instance details

Defined in Network.JSONApi.Resource

FromJSON Relationship Source # 
Instance details

Defined in Network.JSONApi.Resource

type Rep Relationship Source # 
Instance details

Defined in Network.JSONApi.Resource

type Rep Relationship = D1 (MetaData "Relationship" "Network.JSONApi.Resource" "json-api-lib-0.1.1.0-HA2FSjEkbMOH3K6uHch1q9" False) (C1 (MetaCons "Relationship" PrefixI True) (S1 (MetaSel (Just "_data") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Identifier)) :*: S1 (MetaSel (Just "_links") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Links))))

data Resource a 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 (Resource a) Source # 
Instance details

Defined in Network.JSONApi.Resource

Methods

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

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

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

Defined in Network.JSONApi.Resource

Methods

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

show :: Resource a -> String #

showList :: [Resource a] -> ShowS #

Generic (Resource a) Source # 
Instance details

Defined in Network.JSONApi.Resource

Associated Types

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

Methods

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

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

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

Defined in Network.JSONApi.Resource

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

Defined in Network.JSONApi.Resource

HasIdentifier (Resource a) Source # 
Instance details

Defined in Network.JSONApi.Resource

type Rep (Resource a) Source # 
Instance details

Defined in Network.JSONApi.Resource

type Rep (Resource a) = D1 (MetaData "Resource" "Network.JSONApi.Resource" "json-api-lib-0.1.1.0-HA2FSjEkbMOH3K6uHch1q9" False) (C1 (MetaCons "Resource" PrefixI True) ((S1 (MetaSel (Just "getIdentifier") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Identifier) :*: S1 (MetaSel (Just "getResource") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) :*: (S1 (MetaSel (Just "getLinks") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Links)) :*: S1 (MetaSel (Just "getRelationships") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Relationships)))))

class HasIdentifier a where Source #

Typeclass indicating how to access an Identifier for a given datatype

Methods

identifier :: a -> Identifier Source #

Instances
HasIdentifier (Resource a) Source # 
Instance details

Defined in Network.JSONApi.Resource

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 

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 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

Instances
Eq Meta Source # 
Instance details

Defined in Network.JSONApi.Meta

Methods

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

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

Show Meta Source # 
Instance details

Defined in Network.JSONApi.Meta

Methods

showsPrec :: Int -> Meta -> ShowS #

show :: Meta -> String #

showList :: [Meta] -> ShowS #

Generic Meta Source # 
Instance details

Defined in Network.JSONApi.Meta

Associated Types

type Rep Meta :: Type -> Type #

Methods

from :: Meta -> Rep Meta x #

to :: Rep Meta x -> Meta #

ToJSON Meta Source # 
Instance details

Defined in Network.JSONApi.Meta

FromJSON Meta Source # 
Instance details

Defined in Network.JSONApi.Meta

type Rep Meta Source # 
Instance details

Defined in Network.JSONApi.Meta

type Rep Meta = D1 (MetaData "Meta" "Network.JSONApi.Meta" "json-api-lib-0.1.1.0-HA2FSjEkbMOH3K6uHch1q9" True) (C1 (MetaCons "Meta" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Object)))

class ToJSON a => MetaObject a where Source #

Convienience class for constructing a Meta type

Example usage: @ data Pagination = Pagination { currentPage :: Int , totalPages :: Int } deriving (Show, Generic)

instance ToJSON Pagination instance MetaObject Pagination where typeName _ = "pagination" @

Methods

typeName :: a -> Text Source #

Instances
MetaObject Pagination Source # 
Instance details

Defined in Network.JSONApi.Meta

data Pagination Source #

Pagination is arguably a meta object not covered by the Spec. The spec instead opts for links which are supported by this library. However if you would like to throw a generic Pagination meta object into your response payload this type may be used.

mkLinks :: [(Rel, Text)] -> Links Source #

Constructor function for building Links

indexLinks :: ResourcefulEntity e => e -> Maybe Text -> PageSize -> PageNum -> ResourceCount -> Links Source #

Helper function to beuild relative links for a collection of resources of type ResourceEntity.

This helper function assumes that the first page is always page 0.

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

showLink :: ResourcefulEntity e => e -> Links Source #

Helper function to build relative links for a single resource of type ResourceEntity

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

Constructor function for the Document data type.

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

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

mkIncludedResource :: ResourcefulEntity a => a -> Included Source #

Constructor function for the Document data type.

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

mkMeta :: MetaObject a => a -> Meta Source #

Convienience constructor function for the Meta type

Useful on its own or in combination with Meta's monoid instance

Example usage: See MetaSpec.hs for an example