Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class Contravariant f => Selectable f where
- selected :: Selectable f => f lhs -> f rhs -> f (Either lhs rhs)
- class (Divisible f, Representational f) => JSONObjectSerializer f where
- serializeFieldWith :: Text -> (forall jsonSerializer. JSONSerializer jsonSerializer => jsonSerializer a) -> f a
- serializeField :: ToJSON a => Text -> f a
- serializeDescribeFieldWith :: Text -> Text -> (forall valueSerializer. JSONSerializer valueSerializer => valueSerializer a) -> f a
- serializeJust :: Text -> (forall jsonSerializer. JSONSerializer jsonSerializer => jsonSerializer a) -> f (Maybe a)
- class (Divisible f, Representational f) => JSONTupleSerializer f where
- serializeItemWith :: (forall jsonSerializer. JSONSerializer jsonSerializer => jsonSerializer a) -> f a
- serializeItem :: ToJSON a => f a
- class (Selectable f, Representational f) => JSONSerializer f where
- serializeObject :: (forall objSerializer. JSONObjectSerializer objSerializer => objSerializer a) -> f a
- serializeDictionary :: Foldable t => (forall jsonSerializer. JSONSerializer jsonSerializer => jsonSerializer a) -> f (t (Text, a))
- serializeText :: f Text
- serializeTextConstant :: Text -> f a
- serializeNull :: f any
- serializeNumber :: f Scientific
- serializeBool :: f Bool
- serializeTuple :: (forall tupleSerializer. JSONTupleSerializer tupleSerializer => tupleSerializer a) -> f a
- serializeArray :: ToJSON a => f [a]
- nameSerializer :: Text -> f a -> f a
- class ToJSON v where
- toJSON :: forall f. JSONSerializer f => f v
- data ToJSONOptions = ToJSONOptions {}
- defaultToJSONOptions :: ToJSONOptions
- class SpecifiesToJSONOptions (a :: [*]) where
- class GToJSON v where
- gToJSON :: JSONSerializer s => ToJSONOptions -> s (v a)
- sumToEither :: (l :+: r) a -> Either (l a) (r a)
- class GToJSONObject v where
- gToJSONObject :: JSONObjectSerializer f => ToJSONOptions -> f (v a)
- class GToJSONTuple v where
- gToJSONTuple :: JSONTupleSerializer f => ToJSONOptions -> f (v a)
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.
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
Selectable JSONBuilder Source # | |
Defined in Jordan.ToJSON.Builder 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!
:: 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 |
-> f a |
serializeField :: ToJSON a => Text -> f a Source #
serializeDescribeFieldWith Source #
:: Text | Field key to serialize. |
-> Text | Field description. |
-> (forall valueSerializer. JSONSerializer valueSerializer => valueSerializer a) | Serializer for the field. |
-> f a |
:: 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 #
:: (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.
serializeObject, serializeDictionary, serializeText, serializeTextConstant, serializeNull, serializeNumber, serializeBool, serializeTuple, serializeArray
:: (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 |
-> 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
JSONSerializer JSONBuilder Source # | |
Defined in Jordan.ToJSON.Builder 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 # |
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)
Nothing
toJSON :: forall f. JSONSerializer f => f v Source #
Instances
data ToJSONOptions Source #
class SpecifiesToJSONOptions (a :: [*]) where Source #
Instances
SpecifiesToJSONOptions ('[] :: [Type]) Source # | |
Defined in Jordan.ToJSON.Class | |
SpecifiesToJSONOptions xs => SpecifiesToJSONOptions (KeepNothingFields ': xs) Source # | |
Defined in Jordan.ToJSON.Class | |
SpecifiesToJSONOptions xs => SpecifiesToJSONOptions (OmitNothingFields ': xs) Source # | |
Defined in Jordan.ToJSON.Class |
class GToJSON v where Source #
gToJSON :: JSONSerializer s => ToJSONOptions -> s (v a) Source #
Instances
GToJSON (V1 :: Type -> Type) Source # | |
Defined in Jordan.ToJSON.Class gToJSON :: JSONSerializer s => ToJSONOptions -> s (V1 a) Source # | |
(GToJSON (PartOfSum l), GToJSON (PartOfSum r)) => GToJSON (PartOfSum (l :+: r)) Source # | |
Defined in Jordan.ToJSON.Class 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. |
Defined in Jordan.ToJSON.Class gToJSON :: JSONSerializer s => ToJSONOptions -> s (PartOfSum (C1 t f) a) Source # | |
KnownSymbol name => GToJSON (PartOfSum (C1 ('MetaCons name fixity 'False) (U1 :: Type -> Type))) Source # | |
Defined in Jordan.ToJSON.Class 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. |
Defined in Jordan.ToJSON.Class 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. |
Defined in Jordan.ToJSON.Class 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. |
Defined in Jordan.ToJSON.Class 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. |
Defined in Jordan.ToJSON.Class | |
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. |
Defined in Jordan.ToJSON.Class 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. |
Defined in Jordan.ToJSON.Class 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. |
Defined in Jordan.ToJSON.Class 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.
gToJSONObject :: JSONObjectSerializer f => ToJSONOptions -> f (v a) Source #
Instances
(GToJSONObject lhs, GToJSONObject rhs) => GToJSONObject (lhs :*: rhs) Source # | |
Defined in Jordan.ToJSON.Class gToJSONObject :: JSONObjectSerializer f => ToJSONOptions -> f ((lhs :*: rhs) a) Source # | |
(GToJSON f, KnownSymbol selector) => GToJSONObject (S1 ('MetaSel ('Just selector) su ss ds) f) Source # | |
Defined in Jordan.ToJSON.Class 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 # | |
Defined in Jordan.ToJSON.Class gToJSONObject :: JSONObjectSerializer f => ToJSONOptions -> f (S1 ('MetaSel ('Just selector) su ss ds) (Rec0 (Maybe a)) a0) Source # |
class GToJSONTuple v where Source #
gToJSONTuple :: JSONTupleSerializer f => ToJSONOptions -> f (v a) Source #
Instances
(GToJSONTuple lhs, GToJSONTuple rhs) => GToJSONTuple (lhs :*: rhs) Source # | |
Defined in Jordan.ToJSON.Class gToJSONTuple :: JSONTupleSerializer f => ToJSONOptions -> f ((lhs :*: rhs) a) Source # | |
GToJSON f => GToJSONTuple (S1 ('MetaSel ('Nothing :: Maybe Symbol) su ss ds) f) Source # | |
Defined in Jordan.ToJSON.Class gToJSONTuple :: JSONTupleSerializer f0 => ToJSONOptions -> f0 (S1 ('MetaSel 'Nothing su ss ds) f a) Source # |