Safe Haskell | None |
---|---|
Language | Haskell2010 |
Base module!
Has all functionality for parsing and serializing JSON.
Synopsis
- class FromJSON value where
- fromJSON :: JSONParser f => f value
- class (Functor f, forall a. Semigroup (f a), Representational f) => JSONParser f where
- parseObject :: (forall objectParser. JSONObjectParser objectParser => objectParser a) -> f a
- parseObjectStrict :: (forall objectParser. JSONObjectParser objectParser => objectParser a) -> f a
- parseDictionary :: (forall jsonParser. JSONParser jsonParser => jsonParser a) -> f [(Text, a)]
- parseText :: f Text
- parseTextConstant :: Text -> f ()
- parseTuple :: (forall arrayParser. JSONTupleParser arrayParser => arrayParser o) -> f o
- parseArray :: FromJSON a => f [a]
- parseArrayWith :: (forall jsonParser. JSONParser jsonParser => jsonParser a) -> f [a]
- parseNumber :: f Scientific
- parseInteger :: f Integer
- parseNull :: f ()
- parseBool :: f Bool
- validateJSON :: f (Either Text a) -> f a
- nameParser :: Text -> f a -> f a
- addFormat :: Text -> f a -> f a
- class (Applicative f, Representational f) => JSONObjectParser f where
- parseFieldWith :: Text -> (forall valueParser. JSONParser valueParser => valueParser a) -> f a
- parseDescribeFieldWith :: Text -> Text -> (forall valueParser. JSONParser valueParser => valueParser a) -> f a
- parseField :: FromJSON v => Text -> f v
- parseDescribeField :: FromJSON v => Text -> Text -> f v
- parseFieldWithDefault :: Text -> (forall valueParser. JSONParser valueParser => valueParser a) -> a -> f a
- parseDescribeFieldWithDefault :: Text -> Text -> (forall valueParser. JSONParser valueParser => valueParser a) -> a -> f a
- class (Applicative f, Representational f) => JSONTupleParser f where
- consumeItemWith :: (forall valueParser. JSONParser valueParser => valueParser a) -> f a
- consumeItem :: FromJSON v => f v
- parseViaAttoparsec :: forall val. FromJSON val => ByteString -> Either String val
- parseViaAttoparsecWith :: (forall parser. JSONParser parser => parser a) -> ByteString -> Either String a
- attoparsecParser :: FromJSON val => Parser val
- attoparsecParserFor :: (forall parser. JSONParser parser => parser a) -> Parser a
- parseOrReport :: FromJSON a => ByteString -> Either JSONError a
- parseOrReportWith :: (forall parser. JSONParser parser => parser a) -> ByteString -> Either JSONError a
- gFromJSON :: (GFromJSON v, JSONParser f) => FromJSONOptions -> f (v a)
- data FromJSONOptions = FromJSONOptions {}
- class ToJSON v where
- toJSON :: forall f. JSONSerializer f => f v
- 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 (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 Contravariant (f :: Type -> Type) where
- class Contravariant f => Divisible (f :: Type -> Type) where
- class Contravariant f => Selectable f where
- toJSONAsBuilder :: ToJSON a => a -> Builder
- toJSONViaBuilder :: ToJSON a => a -> ByteString
- gToJSON :: (GToJSON v, JSONSerializer s) => ToJSONOptions -> s (v a)
- data ToJSONOptions = ToJSONOptions {}
- data JSONValue
- newtype WithOptions (options :: [*]) a = WithOptions {
- getWithOptions :: a
- data OmitNothingFields
- data KeepNothingFields
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
Nothing
fromJSON :: JSONParser f => f value Source #
Instances
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.
parseObject, parseDictionary, parseText, parseTuple, parseArrayWith, parseNumber, parseNull, parseBool, validateJSON
:: (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.
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 #
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.
:: 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 #
:: 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 #
:: 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 #
:: 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.
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.
parseOrReport :: FromJSON a => ByteString -> Either JSONError a Source #
parseOrReportWith :: (forall parser. JSONParser parser => parser a) -> ByteString -> Either JSONError a Source #
Generically
gFromJSON :: (GFromJSON v, JSONParser f) => FromJSONOptions -> f (v a) Source #
data FromJSONOptions Source #
Instances
Generic FromJSONOptions Source # | |
Defined in Jordan.FromJSON.Class type Rep FromJSONOptions :: Type -> Type # from :: FromJSONOptions -> Rep FromJSONOptions x # to :: Rep FromJSONOptions x -> FromJSONOptions # | |
type Rep FromJSONOptions Source # | |
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
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
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 # |
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.
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:
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.
Instances
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
b
s into a
s (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
String
s and Int
s. 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
divide :: (a -> (b, c)) -> f b -> f c -> f a #
Conquer acts as an identity for combining Divisible
functors.
Instances
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 # |
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
gToJSON :: (GToJSON v, JSONSerializer s) => ToJSONOptions -> s (v a) Source #
data ToJSONOptions Source #
Parsing or Serializing Arbitrary JSON
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
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)
Instances
data OmitNothingFields Source #
Newtype for use with GeneralizedNewtypeDeriving. Will have us omit Nothing fields for parsing and serializing.
Instances
SpecifiesFromJSONOptions xs => SpecifiesFromJSONOptions (OmitNothingFields ': xs) Source # | |
Defined in Jordan.FromJSON.Class | |
SpecifiesToJSONOptions xs => SpecifiesToJSONOptions (OmitNothingFields ': xs) Source # | |
Defined in Jordan.ToJSON.Class |
data KeepNothingFields Source #
Keep nothing fields.
Will have us omit null
when serializing Maybe types.
Instances
SpecifiesFromJSONOptions xs => SpecifiesFromJSONOptions (KeepNothingFields ': xs) Source # | |
Defined in Jordan.FromJSON.Class | |
SpecifiesToJSONOptions xs => SpecifiesToJSONOptions (KeepNothingFields ': xs) Source # | |
Defined in Jordan.ToJSON.Class |