jordan-0.2.0.0: JSON with Structure
Safe HaskellNone
LanguageHaskell2010

Jordan.ToJSON.Class

Synopsis

Documentation

class Contravariant f => Selectable f where Source #

Basically just Decidable but without a superclass constraint that we cannot implement for JSON.

More specifically, we can quite easily serialize some object into either a string or a number as a top-level JSON value, but we cannot serialize both a string and a number as a top level key. This means that we cannot implement Divisible, but we can implement all the operations from Decidable.

This class lets us decide without being able to divide, which is fun to say.

Methods

giveUp :: (arg -> Void) -> f arg Source #

Give up trying to decide.

select :: (arg -> Either lhs rhs) -> f lhs -> f rhs -> f arg Source #

Pick one thing, or another, as long as you can serialize both options.

Instances

Instances details
Selectable JSONBuilder Source # 
Instance details

Defined in Jordan.ToJSON.Builder

Methods

giveUp :: (arg -> Void) -> JSONBuilder arg Source #

select :: (arg -> Either lhs rhs) -> JSONBuilder lhs -> JSONBuilder rhs -> JSONBuilder arg Source #

selected :: Selectable f => f lhs -> f rhs -> f (Either lhs rhs) Source #

class (Divisible f, Representational f) => JSONObjectSerializer f where Source #

An abstract representation of how to serialize a JSON object. Since serializing is the exact opposite of parsing, we have to be Decidable instead of Alternative.

That is, if we are serializing a JSON object, we need to be able to break things apart.

Unfortunately the combinators for breaking things apart are more annoying to use than the combinators for putting things together, and involve a lot of tuples everywhere.

Thankfully we provide a good interface to derive these classes generically!

Minimal complete definition

serializeFieldWith, serializeJust

Methods

serializeFieldWith Source #

Arguments

:: Text

Label for the field to serialize

-> (forall jsonSerializer. JSONSerializer jsonSerializer => jsonSerializer a)

How to serialize the field. The forall ensures that JSON serialization is kept completely abstract. You can only use the methods of JSONSerializer here.

-> f a 

serializeField :: ToJSON a => Text -> f a Source #

serializeDescribeFieldWith Source #

Arguments

:: Text

Field key to serialize.

-> Text

Field description.

-> (forall valueSerializer. JSONSerializer valueSerializer => valueSerializer a)

Serializer for the field.

-> f a 

serializeJust Source #

Arguments

:: Text

Label for the field to serialize

-> (forall jsonSerializer. JSONSerializer jsonSerializer => jsonSerializer a)

Serializer for Just

-> f (Maybe a) 

Write if we have Just a value. Do not add the field otherwise.

class (Divisible f, Representational f) => JSONTupleSerializer f where Source #

Minimal complete definition

serializeItemWith

Methods

serializeItemWith Source #

Arguments

:: (forall jsonSerializer. JSONSerializer jsonSerializer => jsonSerializer a)

Write a single item into the tuple. The forall keeps things abstract.

-> f a 

serializeItem :: ToJSON a => f a Source #

class (Selectable f, Representational f) => JSONSerializer f where Source #

An abstract representation of how to serialize a Haskell value into JSON.

Methods

serializeObject Source #

Arguments

:: (forall objSerializer. JSONObjectSerializer objSerializer => objSerializer a)

How to serialize the object. The forall here keeps things abstract: you are only allowed to use the methods of JSONObjectSerializer here.

-> f a 

serializeDictionary :: Foldable t => (forall jsonSerializer. JSONSerializer jsonSerializer => jsonSerializer a) -> f (t (Text, a)) Source #

serializeText :: f Text Source #

serializeTextConstant :: Text -> f a Source #

Serialize some text constant. Note that this returns a serializer of anything: if you are always going to serialize out the same string, we don't need to even look at the thing we're serializing!

serializeNull :: f any Source #

serializeNumber :: f Scientific Source #

serializeBool :: f Bool Source #

serializeTuple :: (forall tupleSerializer. JSONTupleSerializer tupleSerializer => tupleSerializer a) -> f a Source #

serializeArray :: ToJSON a => f [a] Source #

nameSerializer :: Text -> f a -> f a Source #

Give a name to a serializer. Should be globally unique, if possible.

Instances

Instances details
JSONSerializer JSONBuilder Source # 
Instance details

Defined in Jordan.ToJSON.Builder

Methods

serializeObject :: (forall (objSerializer :: Type -> Type). JSONObjectSerializer objSerializer => objSerializer a) -> JSONBuilder a Source #

serializeDictionary :: Foldable t => (forall (jsonSerializer :: Type -> Type). JSONSerializer jsonSerializer => jsonSerializer a) -> JSONBuilder (t (Text, a)) Source #

serializeText :: JSONBuilder Text Source #

serializeTextConstant :: Text -> JSONBuilder a Source #

serializeNull :: JSONBuilder any Source #

serializeNumber :: JSONBuilder Scientific Source #

serializeBool :: JSONBuilder Bool Source #

serializeTuple :: (forall (tupleSerializer :: Type -> Type). JSONTupleSerializer tupleSerializer => tupleSerializer a) -> JSONBuilder a Source #

serializeArray :: ToJSON a => JSONBuilder [a] Source #

nameSerializer :: Text -> JSONBuilder a -> JSONBuilder a Source #

class ToJSON v where Source #

A class to provide the canonical way to encode a JSON.

This class uses finally tagless style to keep the instructions for serializing abstract. This allows us to automatically generate documentation, and to generate serializers that always avoid the need for intermediate structures.

This class is derivable generically, and will generate a "nice" format. In my opinion, at least.

If you want to customize this JSON, the newtype WithOptions can be helpful, as it allows you to specify options for the generic serialization. Unfortunately, due to a weird GHC quirk, you need to use it with -XStandaloneDeriving as well as -XDerivingVia . That is, you should write:

data PersonFilter = PersonFilter { filterFirstName :: Maybe Text, filterLastName :: Maybe Text }
  deriving (Show, Read, Eq, Ord, Generic)

deriving via (WithOptions '[KeepNothingFields] PersonFilter) instance (ToJSON PersonFilter)

Minimal complete definition

Nothing

Methods

toJSON :: forall f. JSONSerializer f => f v Source #

default toJSON :: (Generic v, GToJSON (Rep v), Typeable v) => JSONSerializer f => f v Source #

Instances

Instances details
ToJSON Bool Source # 
Instance details

Defined in Jordan.ToJSON.Class

Methods

toJSON :: JSONSerializer f => f Bool Source #

ToJSON Double Source # 
Instance details

Defined in Jordan.ToJSON.Class

ToJSON Float Source # 
Instance details

Defined in Jordan.ToJSON.Class

ToJSON Int Source # 
Instance details

Defined in Jordan.ToJSON.Class

Methods

toJSON :: JSONSerializer f => f Int Source #

ToJSON Integer Source # 
Instance details

Defined in Jordan.ToJSON.Class

ToJSON () Source # 
Instance details

Defined in Jordan.ToJSON.Class

Methods

toJSON :: JSONSerializer f => f () Source #

ToJSON All Source # 
Instance details

Defined in Jordan.ToJSON.Class

Methods

toJSON :: JSONSerializer f => f All Source #

ToJSON Any Source # 
Instance details

Defined in Jordan.ToJSON.Class

Methods

toJSON :: JSONSerializer f => f Any Source #

ToJSON String Source # 
Instance details

Defined in Jordan.ToJSON.Class

ToJSON Scientific Source # 
Instance details

Defined in Jordan.ToJSON.Class

ToJSON Text Source # 
Instance details

Defined in Jordan.ToJSON.Class

Methods

toJSON :: JSONSerializer f => f Text Source #

ToJSON JSONType Source # 
Instance details

Defined in Jordan.Types.JSONType

ToJSON JSONArrayError Source # 
Instance details

Defined in Jordan.Types.JSONError

ToJSON JSONObjectError Source # 
Instance details

Defined in Jordan.Types.JSONError

ToJSON JSONError Source # 
Instance details

Defined in Jordan.Types.JSONError

ToJSON JSONValue Source # 
Instance details

Defined in Jordan.Types.JSONValue

ToJSON a => ToJSON [a] Source # 
Instance details

Defined in Jordan.ToJSON.Class

Methods

toJSON :: JSONSerializer f => f [a] Source #

ToJSON a => ToJSON (Maybe a) Source #

Nothings get serialized as null.

Instance details

Defined in Jordan.ToJSON.Class

Methods

toJSON :: JSONSerializer f => f (Maybe a) Source #

(ToJSON a, Typeable a) => ToJSON (Ratio a) Source # 
Instance details

Defined in Jordan.ToJSON.Class

Methods

toJSON :: JSONSerializer f => f (Ratio a) Source #

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

Defined in Jordan.ToJSON.Class

Methods

toJSON :: JSONSerializer f => f (Min a) Source #

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

Defined in Jordan.ToJSON.Class

Methods

toJSON :: JSONSerializer f => f (Max a) Source #

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

Defined in Jordan.ToJSON.Class

Methods

toJSON :: JSONSerializer f => f (First a) Source #

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

Defined in Jordan.ToJSON.Class

Methods

toJSON :: JSONSerializer f => f (Last a) Source #

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

Defined in Jordan.ToJSON.Class

Methods

toJSON :: JSONSerializer f => f (Dual a) Source #

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

Defined in Jordan.ToJSON.Class

Methods

toJSON :: JSONSerializer f => f (Sum a) Source #

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

Defined in Jordan.ToJSON.Class

Methods

toJSON :: JSONSerializer f => f (Product a) Source #

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

Defined in Jordan.ToJSON.Class

Methods

toJSON :: JSONSerializer f => f (NonEmpty a) Source #

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

Defined in Jordan.ToJSON.Class

Methods

toJSON :: JSONSerializer f => f (Set a) Source #

(ToJSON lhs, ToJSON rhs) => ToJSON (Either lhs rhs) Source # 
Instance details

Defined in Jordan.ToJSON.Class

Methods

toJSON :: JSONSerializer f => f (Either lhs rhs) Source #

ToJSON a => ToJSON (Map Integer a) Source # 
Instance details

Defined in Jordan.ToJSON.Class

Methods

toJSON :: JSONSerializer f => f (Map Integer a) Source #

ToJSON a => ToJSON (Map Text a) Source # 
Instance details

Defined in Jordan.ToJSON.Class

Methods

toJSON :: JSONSerializer f => f (Map Text a) Source #

(Generic a, GToJSON (Rep a), Typeable a, SpecifiesToJSONOptions options) => ToJSON (WithOptions options a) Source # 
Instance details

Defined in Jordan.ToJSON.Class

Methods

toJSON :: JSONSerializer f => f (WithOptions options a) Source #

class GToJSON v where Source #

Methods

gToJSON :: JSONSerializer s => ToJSONOptions -> s (v a) Source #

Instances

Instances details
GToJSON (V1 :: Type -> Type) Source # 
Instance details

Defined in Jordan.ToJSON.Class

Methods

gToJSON :: JSONSerializer s => ToJSONOptions -> s (V1 a) Source #

(GToJSON (PartOfSum l), GToJSON (PartOfSum r)) => GToJSON (PartOfSum (l :+: r)) Source # 
Instance details

Defined in Jordan.ToJSON.Class

Methods

gToJSON :: JSONSerializer s => ToJSONOptions -> s (PartOfSum (l :+: r) a) Source #

(Constructor t, GToJSON (C1 t f)) => GToJSON (PartOfSum (C1 t f)) Source #

When rendering a sum type, and this is NOT an enum value, render via the sum encoding option the user provided.

Instance details

Defined in Jordan.ToJSON.Class

Methods

gToJSON :: JSONSerializer s => ToJSONOptions -> s (PartOfSum (C1 t f) a) Source #

KnownSymbol name => GToJSON (PartOfSum (C1 ('MetaCons name fixity 'False) (U1 :: Type -> Type))) Source # 
Instance details

Defined in Jordan.ToJSON.Class

Methods

gToJSON :: JSONSerializer s => ToJSONOptions -> s (PartOfSum (C1 ('MetaCons name fixity 'False) U1) a) Source #

ToJSON c => GToJSON (K1 i c :: Type -> Type) Source #

Top-level metadata is ignored.

Instance details

Defined in Jordan.ToJSON.Class

Methods

gToJSON :: JSONSerializer s => ToJSONOptions -> s (K1 i c a) Source #

(GToJSON (PartOfSum l), GToJSON (PartOfSum r)) => GToJSON (l :+: r) Source #

If we can serialize out both sides of a sum-type, we can serialize out the sum type.

Instance details

Defined in Jordan.ToJSON.Class

Methods

gToJSON :: JSONSerializer s => ToJSONOptions -> s ((l :+: r) a) Source #

(GToJSON f, Datatype t) => GToJSON (D1 t f) Source #

Datatype metadata: we name the overall datatype with the baseName passed in the options, then serialize the inner information.

Instance details

Defined in Jordan.ToJSON.Class

Methods

gToJSON :: JSONSerializer s => ToJSONOptions -> s (D1 t f a) Source #

ToJSON i => GToJSON (C1 ('MetaCons n s 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) su ss ds) (Rec0 i))) Source #

If we have a single-argument constructor with no selectors, we want to just parse it directly.

Instance details

Defined in Jordan.ToJSON.Class

Methods

gToJSON :: JSONSerializer s0 => ToJSONOptions -> s0 (C1 ('MetaCons n s 'False) (S1 ('MetaSel 'Nothing su ss ds) (Rec0 i)) a) Source #

KnownSymbol name => GToJSON (C1 ('MetaCons name fixity 'False) (U1 :: Type -> Type)) Source #

Serialize out a no-argument constructor via a string value of its name. This allows us to serialize out enum keys more easily.

This does not get a unique name as recursion cannot happen.

Instance details

Defined in Jordan.ToJSON.Class

Methods

gToJSON :: JSONSerializer s => ToJSONOptions -> s (C1 ('MetaCons name fixity 'False) U1 a) Source #

(GToJSONObject inner, Constructor ('MetaCons n s 'True)) => GToJSON (C1 ('MetaCons n s 'True) inner) Source #

If we have a constructor with arguments AND selectors (IE, a record), then we serialize out a JSON object.

Instance details

Defined in Jordan.ToJSON.Class

Methods

gToJSON :: JSONSerializer s0 => ToJSONOptions -> s0 (C1 ('MetaCons n s 'True) inner a) Source #

(GToJSONTuple inner, Constructor ('MetaCons n s 'False)) => GToJSON (C1 ('MetaCons n s 'False) inner) Source #

IF we have a constructor with arguments, but not selectors, then we serialize as a tuple.

Instance details

Defined in Jordan.ToJSON.Class

Methods

gToJSON :: JSONSerializer s0 => ToJSONOptions -> s0 (C1 ('MetaCons n s 'False) inner a) Source #

sumToEither :: (l :+: r) a -> Either (l a) (r a) Source #

class GToJSONObject v where Source #

Type class for generically converting to a JSON object. We can do this if all the fields under a constructor are named.

Instances

Instances details
(GToJSONObject lhs, GToJSONObject rhs) => GToJSONObject (lhs :*: rhs) Source # 
Instance details

Defined in Jordan.ToJSON.Class

Methods

gToJSONObject :: JSONObjectSerializer f => ToJSONOptions -> f ((lhs :*: rhs) a) Source #

(GToJSON f, KnownSymbol selector) => GToJSONObject (S1 ('MetaSel ('Just selector) su ss ds) f) Source # 
Instance details

Defined in Jordan.ToJSON.Class

Methods

gToJSONObject :: JSONObjectSerializer f0 => ToJSONOptions -> f0 (S1 ('MetaSel ('Just selector) su ss ds) f a) Source #

(ToJSON a, KnownSymbol selector) => GToJSONObject (S1 ('MetaSel ('Just selector) su ss ds) (Rec0 (Maybe a))) Source # 
Instance details

Defined in Jordan.ToJSON.Class

Methods

gToJSONObject :: JSONObjectSerializer f => ToJSONOptions -> f (S1 ('MetaSel ('Just selector) su ss ds) (Rec0 (Maybe a)) a0) Source #

class GToJSONTuple v where Source #

Instances

Instances details
(GToJSONTuple lhs, GToJSONTuple rhs) => GToJSONTuple (lhs :*: rhs) Source # 
Instance details

Defined in Jordan.ToJSON.Class

Methods

gToJSONTuple :: JSONTupleSerializer f => ToJSONOptions -> f ((lhs :*: rhs) a) Source #

GToJSON f => GToJSONTuple (S1 ('MetaSel ('Nothing :: Maybe Symbol) su ss ds) f) Source # 
Instance details

Defined in Jordan.ToJSON.Class

Methods

gToJSONTuple :: JSONTupleSerializer f0 => ToJSONOptions -> f0 (S1 ('MetaSel 'Nothing su ss ds) f a) Source #