jordan-0.2.0.0: JSON with Structure
Safe HaskellNone
LanguageHaskell2010

Jordan

Description

Base module!

Has all functionality for parsing and serializing JSON.

Synopsis

JSON Parsing

Abstractly

class FromJSON value where Source #

A class to provide the canonical way to parse a JSON. This class uses finally tagless tyle to keep the instructions for parsing abstract. This allows us to automatically generate documentation, and to generate parsers that do not use 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 (FromJSON PersonFilter)

Laws

Expand

This instance is lawless, unless ToJSON is also defined for this type. In that case, the representation parsed by FromJSON should match that of the representation serialized by ToJSON.

Minimal complete definition

Nothing

Methods

fromJSON :: JSONParser f => f value Source #

default fromJSON :: (Generic value, GFromJSON (Rep value), Typeable value) => JSONParser f => f value Source #

Instances

Instances details
FromJSON Bool Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f Bool Source #

FromJSON Double Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f Double Source #

FromJSON Float Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f Float Source #

FromJSON Int Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f Int Source #

FromJSON Int32 Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f Int32 Source #

FromJSON Int64 Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f Int64 Source #

FromJSON Integer Source # 
Instance details

Defined in Jordan.FromJSON.Class

FromJSON () Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f () Source #

FromJSON All Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f All Source #

FromJSON Any Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f Any Source #

FromJSON String Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f String Source #

FromJSON Scientific Source # 
Instance details

Defined in Jordan.FromJSON.Class

FromJSON Text Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f Text Source #

FromJSON JSONType Source # 
Instance details

Defined in Jordan.Types.JSONType

FromJSON JSONArrayError Source # 
Instance details

Defined in Jordan.Types.JSONError

FromJSON JSONObjectError Source # 
Instance details

Defined in Jordan.Types.JSONError

FromJSON JSONError Source # 
Instance details

Defined in Jordan.Types.JSONError

FromJSON JSONValue Source # 
Instance details

Defined in Jordan.Types.JSONValue

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

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f [a] Source #

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

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f (Maybe a) Source #

(Integral a, FromJSON a) => FromJSON (Ratio a) Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f (Ratio a) Source #

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

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f (Min a) Source #

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

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f (Max a) Source #

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

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f (First a) Source #

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

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f (Last a) Source #

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

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f (First a) Source #

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

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f (Last a) Source #

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

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f (Dual a) Source #

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

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f (Sum a) Source #

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

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f (Product a) Source #

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

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f (NonEmpty a) Source #

(FromJSON a, Ord a) => FromJSON (Set a) Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f (Set a) Source #

(FromJSON l, FromJSON r) => FromJSON (Either l r) Source #

Right-biased: will try to parse a Right value first.

Instance details

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f (Either l r) Source #

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

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f (Map Integer a) Source #

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

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f (Map Text a) Source #

(Generic a, GFromJSON (Rep a), Typeable a, SpecifiesFromJSONOptions options) => FromJSON (WithOptions options a) Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f (WithOptions options a) Source #

FromJSON (f a) => FromJSON (Ap f a) Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f0 => f0 (Ap f a) Source #

FromJSON (f a) => FromJSON (Alt f a) Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f0 => f0 (Alt f a) Source #

class (Functor f, forall a. Semigroup (f a), Representational f) => JSONParser f where Source #

Abstract class representing various parsers.

All parsers must have a Monoid instance that represents choice with failure as the identity.

Methods

parseObject Source #

Arguments

:: (forall objectParser. JSONObjectParser objectParser => objectParser a)

Instructions on how to parse the object. Note that the actual implementation is kept abstract: you can only use methods found in JSONObjectParser, or combinators of those methods. This ensures that we can generate the proper parser in all cases.

-> f a 

parseObjectStrict :: (forall objectParser. JSONObjectParser objectParser => objectParser a) -> f a Source #

Parse an object where you are okay if we parse strictly, IE, do not allow extra fields. This sometimes enables us to generate parsers that run faster.

parseDictionary :: (forall jsonParser. JSONParser jsonParser => jsonParser a) -> f [(Text, a)] Source #

Parse a dictionary of key-value pairs.

parseText :: f Text Source #

Parse a text field.

parseTextConstant :: Text -> f () Source #

parseTuple :: (forall arrayParser. JSONTupleParser arrayParser => arrayParser o) -> f o Source #

Use a tuple parser to parse an array.

parseArray :: FromJSON a => f [a] Source #

parseArrayWith :: (forall jsonParser. JSONParser jsonParser => jsonParser a) -> f [a] Source #

parseNumber :: f Scientific Source #

parseInteger :: f Integer Source #

parseNull :: f () Source #

parseBool :: f Bool Source #

validateJSON :: f (Either Text a) -> f a Source #

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

Give a parser a unique name. May be used for documentation.

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

Add information about the format of a particular parser.

class (Applicative f, Representational f) => JSONObjectParser f where Source #

A class for parsing JSON objects.

Minimal complete definition

parseFieldWith, parseFieldWithDefault

Methods

parseFieldWith Source #

Arguments

:: Text

Label of the field. Will be parsed into escaped text, if need be.

-> (forall valueParser. JSONParser valueParser => valueParser a)

How to parse the field. Note the forall in this type signature: you cannot have this be specific to any particular implementation of parsing, to keep the parsing of a JSON abstract.

-> f a 

Parse an object field with a given label, using a parser.

Note: in order to enable the generation of better documentation, use parseField instead if at all possible!

parseDescribeFieldWith Source #

Arguments

:: Text

Field key to parse

-> Text

Description of the field

-> (forall valueParser. JSONParser valueParser => valueParser a)

Parser for the field

-> f a 

parseField :: FromJSON v => Text -> f v Source #

parseDescribeField :: FromJSON v => Text -> Text -> f v Source #

parseFieldWithDefault Source #

Arguments

:: Text

Label of the field.

-> (forall valueParser. JSONParser valueParser => valueParser a)

Parse the value from the field

-> a

Default value for the field

-> f a

Field in the object.

parseDescribeFieldWithDefault Source #

Arguments

:: Text

Label of the field

-> Text

Description of the field

-> (forall valueParser. JSONParser valueParser => valueParser a)

Parser for the field

-> a 
-> f a 

class (Applicative f, Representational f) => JSONTupleParser f where Source #

A class for parsing JSON arrays.

Minimal complete definition

consumeItemWith

Methods

consumeItemWith :: (forall valueParser. JSONParser valueParser => valueParser a) -> f a Source #

Use a JSON parser to consume a single item of an array, then move onto the next one.

Note: you should prefer consumeItem as it enables better documentation generation.

consumeItem :: FromJSON v => f v Source #

Consume a single array item.

Concretely

Via Attoparsec

These parsers use the excellent Attoparsec library to do their work. This means that they're quite fast, but that they also provide less-than-ideal error messages. You should use these when speed is needed, or when you're reasonably certain that nobody will make a mistake. APIs intended only for internal use, for example.

parseViaAttoparsec :: forall val. FromJSON val => ByteString -> Either String val Source #

Parse a ByteString via an Attoparsec Parser.

parseViaAttoparsecWith :: (forall parser. JSONParser parser => parser a) -> ByteString -> Either String a Source #

attoparsecParser :: FromJSON val => Parser val Source #

Get an Attoparsec parser for a particular JSON-parsable value.

attoparsecParserFor :: (forall parser. JSONParser parser => parser a) -> Parser a Source #

Convert an abstract JSON parser to an Attoparsec Parser. This function will skip leading whitespace.

With Error Reporting

These parsers parse to either a value or an *error report*, which is a detailed report of what exactly what wrong. This uses a roll-our-own parsing library based on *unboxed sums*. It's been tested via QuickCheck, but it is doing some spooky-scary raw pointer opertions.

This is a bit slower than the attoparsec parser, but *much* better at error handling. Use it for external-facing APIs---assuming that you trust my ability to write primops.

parseOrReportWith :: (forall parser. JSONParser parser => parser a) -> ByteString -> Either JSONError a Source #

Generically

data FromJSONOptions Source #

Instances

Instances details
Generic FromJSONOptions Source # 
Instance details

Defined in Jordan.FromJSON.Class

Associated Types

type Rep FromJSONOptions :: Type -> Type #

type Rep FromJSONOptions Source # 
Instance details

Defined in Jordan.FromJSON.Class

type Rep FromJSONOptions = D1 ('MetaData "FromJSONOptions" "Jordan.FromJSON.Class" "jordan-0.2.0.0-inplace" 'False) (C1 ('MetaCons "FromJSONOptions" 'PrefixI 'True) ((S1 ('MetaSel ('Just "fromJSONEncodeSums") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SumTypeEncoding) :*: S1 ('MetaSel ('Just "fromJSONBaseName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :*: (S1 ('MetaSel ('Just "convertEnum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (String -> String)) :*: S1 ('MetaSel ('Just "fromJSONOmitNothingFields") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))

JSON Serialization

Abstractly

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

Re-Exports for Serialization

class Contravariant (f :: Type -> Type) where #

The class of contravariant functors.

Whereas in Haskell, one can think of a Functor as containing or producing values, a contravariant functor is a functor that can be thought of as consuming values.

As an example, consider the type of predicate functions a -> Bool. One such predicate might be negative x = x < 0, which classifies integers as to whether they are negative. However, given this predicate, we can re-use it in other situations, providing we have a way to map values to integers. For instance, we can use the negative predicate on a person's bank balance to work out if they are currently overdrawn:

newtype Predicate a = Predicate { getPredicate :: a -> Bool }

instance Contravariant Predicate where
  contramap f (Predicate p) = Predicate (p . f)
                                         |   `- First, map the input...
                                         `----- then apply the predicate.

overdrawn :: Predicate Person
overdrawn = contramap personBankBalance negative

Any instance should be subject to the following laws:

Identity
contramap id = id
Composition
contramap (g . f) = contramap f . contramap g

Note, that the second law follows from the free theorem of the type of contramap and the first law, so you need only check that the former condition holds.

Minimal complete definition

contramap

Methods

contramap :: (a -> b) -> f b -> f a #

(>$) :: b -> f b -> f a infixl 4 #

Replace all locations in the output with the same value. The default definition is contramap . const, but this may be overridden with a more efficient version.

Instances

Instances details
Contravariant Predicate

A Predicate is a Contravariant Functor, because contramap can apply its function argument to the input of the predicate.

Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Predicate b -> Predicate a #

(>$) :: b -> Predicate b -> Predicate a #

Contravariant Comparison

A Comparison is a Contravariant Functor, because contramap can apply its function argument to each input of the comparison function.

Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Comparison b -> Comparison a #

(>$) :: b -> Comparison b -> Comparison a #

Contravariant Equivalence

Equivalence relations are Contravariant, because you can apply the contramapped function to each input to the equivalence relation.

Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Equivalence b -> Equivalence a #

(>$) :: b -> Equivalence b -> Equivalence a #

Contravariant JSONBuilder Source # 
Instance details

Defined in Jordan.ToJSON.Builder

Methods

contramap :: (a -> b) -> JSONBuilder b -> JSONBuilder a #

(>$) :: b -> JSONBuilder b -> JSONBuilder a #

Contravariant (V1 :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> V1 b -> V1 a #

(>$) :: b -> V1 b -> V1 a #

Contravariant (U1 :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> U1 b -> U1 a #

(>$) :: b -> U1 b -> U1 a #

Contravariant (Op a) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a0 -> b) -> Op a b -> Op a a0 #

(>$) :: b -> Op a b -> Op a a0 #

Contravariant (Proxy :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Proxy b -> Proxy a #

(>$) :: b -> Proxy b -> Proxy a #

Contravariant f => Contravariant (Rec1 f) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Rec1 f b -> Rec1 f a #

(>$) :: b -> Rec1 f b -> Rec1 f a #

Contravariant (Const a :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a0 -> b) -> Const a b -> Const a a0 #

(>$) :: b -> Const a b -> Const a a0 #

Contravariant f => Contravariant (Alt f) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Alt f b -> Alt f a #

(>$) :: b -> Alt f b -> Alt f a #

Contravariant m => Contravariant (ErrorT e m) 
Instance details

Defined in Control.Monad.Trans.Error

Methods

contramap :: (a -> b) -> ErrorT e m b -> ErrorT e m a #

(>$) :: b -> ErrorT e m b -> ErrorT e m a #

Contravariant (K1 i c :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> K1 i c b -> K1 i c a #

(>$) :: b -> K1 i c b -> K1 i c a #

(Contravariant f, Contravariant g) => Contravariant (f :+: g) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> (f :+: g) b -> (f :+: g) a #

(>$) :: b -> (f :+: g) b -> (f :+: g) a #

(Contravariant f, Contravariant g) => Contravariant (f :*: g) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> (f :*: g) b -> (f :*: g) a #

(>$) :: b -> (f :*: g) b -> (f :*: g) a #

(Contravariant f, Contravariant g) => Contravariant (Product f g) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Product f g b -> Product f g a #

(>$) :: b -> Product f g b -> Product f g a #

(Contravariant f, Contravariant g) => Contravariant (Sum f g) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Sum f g b -> Sum f g a #

(>$) :: b -> Sum f g b -> Sum f g a #

Contravariant f => Contravariant (M1 i c f) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> M1 i c f b -> M1 i c f a #

(>$) :: b -> M1 i c f b -> M1 i c f a #

(Functor f, Contravariant g) => Contravariant (f :.: g) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> (f :.: g) b -> (f :.: g) a #

(>$) :: b -> (f :.: g) b -> (f :.: g) a #

(Functor f, Contravariant g) => Contravariant (Compose f g) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Compose f g b -> Compose f g a #

(>$) :: b -> Compose f g b -> Compose f g a #

class Contravariant f => Divisible (f :: Type -> Type) where #

A Divisible contravariant functor is the contravariant analogue of Applicative.

Continuing the intuition that Contravariant functors consume input, a Divisible contravariant functor also has the ability to be composed "beside" another contravariant functor.

Serializers provide a good example of Divisible contravariant functors. To begin let's start with the type of serializers for specific types:

newtype Serializer a = Serializer { runSerializer :: a -> ByteString }

This is a contravariant functor:

instance Contravariant Serializer where
  contramap f s = Serializer (runSerializer s . f)

That is, given a serializer for a (s :: Serializer a), and a way to turn bs into as (a mapping f :: b -> a), we have a serializer for b: contramap f s :: Serializer b.

Divisible gives us a way to combine two serializers that focus on different parts of a structure. If we postulate the existance of two primitive serializers - string :: Serializer String and int :: Serializer Int, we would like to be able to combine these into a serializer for pairs of Strings and Ints. How can we do this? Simply run both serializers and combine their output!

data StringAndInt = StringAndInt String Int

stringAndInt :: Serializer StringAndInt
stringAndInt = Serializer $ \(StringAndInt s i) ->
  let sBytes = runSerializer string s
      iBytes = runSerializer int i
  in sBytes <> iBytes

divide is a generalization by also taking a contramap like function to split any a into a pair. This conveniently allows you to target fields of a record, for instance, by extracting the values under two fields and combining them into a tuple.

To complete the example, here is how to write stringAndInt using a Divisible instance:

instance Divisible Serializer where
  conquer = Serializer (const mempty)

  divide toBC bSerializer cSerializer = Serializer $ \a ->
    case toBC a of
      (b, c) ->
        let bBytes = runSerializer bSerializer b
            cBytes = runSerializer cSerializer c
        in bBytes <> cBytes

stringAndInt :: Serializer StringAndInt
stringAndInt =
  divide (\(StringAndInt s i) -> (s, i)) string int

Methods

divide :: (a -> (b, c)) -> f b -> f c -> f a #

conquer :: f a #

Conquer acts as an identity for combining Divisible functors.

Instances

Instances details
Divisible SettableStateVar 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Divisible Predicate 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> Predicate b -> Predicate c -> Predicate a #

conquer :: Predicate a #

Divisible Comparison 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> Comparison b -> Comparison c -> Comparison a #

conquer :: Comparison a #

Divisible Equivalence 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> Equivalence b -> Equivalence c -> Equivalence a #

conquer :: Equivalence a #

Divisible (U1 :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> U1 b -> U1 c -> U1 a #

conquer :: U1 a #

Monoid r => Divisible (Op r) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> Op r b -> Op r c -> Op r a #

conquer :: Op r a #

Divisible (Proxy :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> Proxy b -> Proxy c -> Proxy a #

conquer :: Proxy a #

Divisible m => Divisible (MaybeT m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> MaybeT m b -> MaybeT m c -> MaybeT m a #

conquer :: MaybeT m a #

Divisible m => Divisible (ListT m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> ListT m b -> ListT m c -> ListT m a #

conquer :: ListT m a #

Divisible f => Divisible (Rec1 f) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> Rec1 f b -> Rec1 f c -> Rec1 f a #

conquer :: Rec1 f a #

Monoid m => Divisible (Const m :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> Const m b -> Const m c -> Const m a #

conquer :: Const m a #

Divisible f => Divisible (Alt f) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> Alt f b -> Alt f c -> Alt f a #

conquer :: Alt f a #

Divisible f => Divisible (Reverse f) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> Reverse f b -> Reverse f c -> Reverse f a #

conquer :: Reverse f a #

Monoid m => Divisible (Constant m :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> Constant m b -> Constant m c -> Constant m a #

conquer :: Constant m a #

Divisible m => Divisible (WriterT w m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> WriterT w m b -> WriterT w m c -> WriterT w m a #

conquer :: WriterT w m a #

Divisible m => Divisible (WriterT w m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> WriterT w m b -> WriterT w m c -> WriterT w m a #

conquer :: WriterT w m a #

Divisible m => Divisible (StateT s m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> StateT s m b -> StateT s m c -> StateT s m a #

conquer :: StateT s m a #

Divisible m => Divisible (StateT s m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> StateT s m b -> StateT s m c -> StateT s m a #

conquer :: StateT s m a #

Divisible m => Divisible (ReaderT r m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> ReaderT r m b -> ReaderT r m c -> ReaderT r m a #

conquer :: ReaderT r m a #

Divisible f => Divisible (IdentityT f) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> IdentityT f b -> IdentityT f c -> IdentityT f a #

conquer :: IdentityT f a #

Divisible m => Divisible (ExceptT e m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> ExceptT e m b -> ExceptT e m c -> ExceptT e m a #

conquer :: ExceptT e m a #

Divisible m => Divisible (ErrorT e m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> ErrorT e m b -> ErrorT e m c -> ErrorT e m a #

conquer :: ErrorT e m a #

Divisible f => Divisible (Backwards f) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> Backwards f b -> Backwards f c -> Backwards f a #

conquer :: Backwards f a #

(Divisible f, Divisible g) => Divisible (f :*: g) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> (f :*: g) b -> (f :*: g) c -> (f :*: g) a #

conquer :: (f :*: g) a #

(Divisible f, Divisible g) => Divisible (Product f g) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> Product f g b -> Product f g c -> Product f g a #

conquer :: Product f g a #

Divisible f => Divisible (M1 i c f) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c0)) -> M1 i c f b -> M1 i c f c0 -> M1 i c f a #

conquer :: M1 i c f a #

(Applicative f, Divisible g) => Divisible (f :.: g) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> (f :.: g) b -> (f :.: g) c -> (f :.: g) a #

conquer :: (f :.: g) a #

(Applicative f, Divisible g) => Divisible (Compose f g) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> Compose f g b -> Compose f g c -> Compose f g a #

conquer :: Compose f g a #

Divisible m => Divisible (RWST r w s m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> RWST r w s m b -> RWST r w s m c -> RWST r w s m a #

conquer :: RWST r w s m a #

Divisible m => Divisible (RWST r w s m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> RWST r w s m b -> RWST r w s m c -> RWST r w s m a #

conquer :: RWST r w s m a #

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 #

Concretely

toJSONAsBuilder :: ToJSON a => a -> Builder Source #

Serialize a Haskell datatype to a Builder.

This is available for performance reasons: you may wish to use hPutBuilder in order to (more or less) directly serialize some JSON object to a file handle.

toJSONViaBuilder :: ToJSON a => a -> ByteString Source #

Serialize a Haskell datatype to a lazy ByteString.

Generically

Parsing or Serializing Arbitrary JSON

data JSONValue Source #

A type for any JSON value. This is a basic Haskell sum type representation.

This is intended to for use when working with JSON where you do not know much about its structure.

Instances

Instances details
Eq JSONValue Source # 
Instance details

Defined in Jordan.Types.JSONValue

Ord JSONValue Source # 
Instance details

Defined in Jordan.Types.JSONValue

Show JSONValue Source # 
Instance details

Defined in Jordan.Types.JSONValue

Generic JSONValue Source # 
Instance details

Defined in Jordan.Types.JSONValue

Associated Types

type Rep JSONValue :: Type -> Type #

FromJSON JSONValue Source # 
Instance details

Defined in Jordan.Types.JSONValue

ToJSON JSONValue Source # 
Instance details

Defined in Jordan.Types.JSONValue

type Rep JSONValue Source # 
Instance details

Defined in Jordan.Types.JSONValue

Newtypes for DerivingVia

newtype WithOptions (options :: [*]) a Source #

A newtype wrapper, designed to make it easier to derive ToJSON and FromJSON instances. The API of abstract JSON serializing is awkward due to the somewhat bad ergonomics of the Divisible and (especially) Decidable typeclasses.

In general, using -XDerivingVia , -XDeriveGeneric , -XDataKinds and this wrapper will make your life much easier. Unfortunately, due to a weird GHC quirk, you also need -XDerivingVia .

That is, the following won't work, complaining about role errors:

 data PersonFilter = PersonFilter { filterFirstName :: Maybe Text, filterLastName :: Maybe Text }
   deriving (Show, Generic)
   deriving (ToJSON, FromJSON) via (WithOptions '[KeepNothingFields] PersonFilter)

But this will:

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

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

Constructors

WithOptions 

Fields

Instances

Instances details
Eq a => Eq (WithOptions options a) Source # 
Instance details

Defined in Jordan.Generic.Options

Methods

(==) :: WithOptions options a -> WithOptions options a -> Bool #

(/=) :: WithOptions options a -> WithOptions options a -> Bool #

Ord a => Ord (WithOptions options a) Source # 
Instance details

Defined in Jordan.Generic.Options

Methods

compare :: WithOptions options a -> WithOptions options a -> Ordering #

(<) :: WithOptions options a -> WithOptions options a -> Bool #

(<=) :: WithOptions options a -> WithOptions options a -> Bool #

(>) :: WithOptions options a -> WithOptions options a -> Bool #

(>=) :: WithOptions options a -> WithOptions options a -> Bool #

max :: WithOptions options a -> WithOptions options a -> WithOptions options a #

min :: WithOptions options a -> WithOptions options a -> WithOptions options a #

Show a => Show (WithOptions options a) Source # 
Instance details

Defined in Jordan.Generic.Options

Methods

showsPrec :: Int -> WithOptions options a -> ShowS #

show :: WithOptions options a -> String #

showList :: [WithOptions options a] -> ShowS #

(Generic a, GFromJSON (Rep a), Typeable a, SpecifiesFromJSONOptions options) => FromJSON (WithOptions options a) Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f (WithOptions options 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 #

data OmitNothingFields Source #

Newtype for use with GeneralizedNewtypeDeriving. Will have us omit Nothing fields for parsing and serializing.

data KeepNothingFields Source #

Keep nothing fields. Will have us omit null when serializing Maybe types.