jordan-0.2.0.0: JSON with Structure
Safe HaskellNone
LanguageHaskell2010

Jordan.FromJSON.Class

Description

Parse JSON using finally-tagless style.

This provides JSON parsing as an abstract interface. This interface provides a way to parse JSON that is *inspectable* and has some nice properties: for example, we can use it to build a parser that directly parses your data structure, without building some intermediate value type!

Synopsis

Documentation

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.

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 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 Text Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f Text Source #

FromJSON String Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f String 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 Scientific Source # 
Instance details

Defined in Jordan.FromJSON.Class

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 #

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-He2CL9yJm8jJiPwP3VkPys" '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))))

class GFromJSON v where Source #

Methods

gFromJSON :: JSONParser f => FromJSONOptions -> f (v a) Source #

Instances

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

Defined in Jordan.FromJSON.Class

Methods

gFromJSON :: JSONParser f => FromJSONOptions -> f (PartOfSum (l :+: r) a) Source #

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

When rendering a sum type, if we have a more complex value (IE, maybe this is a constructor that takes arguments), we want to use whatever sum encoding was provided in the options.

Instance details

Defined in Jordan.FromJSON.Class

Methods

gFromJSON :: JSONParser f0 => FromJSONOptions -> f0 (PartOfSum (C1 t f) a) Source #

KnownSymbol connName => GFromJSON (PartOfSum (C1 ('MetaCons connName dontCare 'False) (U1 :: Type -> Type))) Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

gFromJSON :: JSONParser f => FromJSONOptions -> f (PartOfSum (C1 ('MetaCons connName dontCare 'False) U1) a) Source #

FromJSON c => GFromJSON (K1 i c :: Type -> Type) Source #

Top-level metadata is ignored.

Instance details

Defined in Jordan.FromJSON.Class

Methods

gFromJSON :: JSONParser f => FromJSONOptions -> f (K1 i c a) Source #

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

If we can parse both sides of a sum-type, we can parse the entire sum type.

Instance details

Defined in Jordan.FromJSON.Class

Methods

gFromJSON :: JSONParser f => FromJSONOptions -> f ((l :+: r) a) Source #

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

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

Instance details

Defined in Jordan.FromJSON.Class

Methods

gFromJSON :: JSONParser f0 => FromJSONOptions -> f0 (D1 t f a) Source #

KnownSymbol connName => GFromJSON (C1 ('MetaCons connName dontCare 'False) (U1 :: Type -> Type)) Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

gFromJSON :: JSONParser f => FromJSONOptions -> f (C1 ('MetaCons connName dontCare 'False) U1 a) Source #

(FromJSON inner, KnownSymbol n) => GFromJSON (C1 ('MetaCons n s 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) ss su dl) (Rec0 inner))) Source #

Special-case: a one-argument constructor with no field selector gets its own parser, skipping the tuple entirely.

Instance details

Defined in Jordan.FromJSON.Class

Methods

gFromJSON :: JSONParser f => FromJSONOptions -> f (C1 ('MetaCons n s 'False) (S1 ('MetaSel 'Nothing ss su dl) (Rec0 inner)) a) Source #

(GFromJSONObject i, KnownSymbol n) => GFromJSON (C1 ('MetaCons n s 'True) i) Source #

If we have a constructor with arguments, and those arguments do have selectors (IE, this is a record), then we should parse as a record.

Instance details

Defined in Jordan.FromJSON.Class

Methods

gFromJSON :: JSONParser f => FromJSONOptions -> f (C1 ('MetaCons n s 'True) i a) Source #

(GFromJSONTuple inner, KnownSymbol n) => GFromJSON (C1 ('MetaCons n s 'False) inner) Source #

If we have a constructor with arguments, and those arguments do not have selectors (IE, this is not a record), then we should parse as a tuple.

Instance details

Defined in Jordan.FromJSON.Class

Methods

gFromJSON :: JSONParser f => FromJSONOptions -> f (C1 ('MetaCons n s 'False) inner a) Source #

class GFromJSONObject v where Source #

Class that helps us parse JSON objects.

Instances

Instances details
GFromJSONObject (U1 :: Type -> Type) Source # 
Instance details

Defined in Jordan.FromJSON.Class

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

Defined in Jordan.FromJSON.Class

Methods

gFromJSONObject :: JSONObjectParser f => FromJSONOptions -> f ((lhs :*: rhs) a) Source #

(FromJSON c, Selector t) => GFromJSONObject (S1 t (K1 v (Maybe c) :: Type -> Type)) Source # 
Instance details

Defined in Jordan.FromJSON.Class

(FromJSON c, Selector t) => GFromJSONObject (S1 t (K1 v c :: Type -> Type)) Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

gFromJSONObject :: JSONObjectParser f => FromJSONOptions -> f (S1 t (K1 v c) a) Source #

class GFromJSONTuple v where Source #

Instances

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

Defined in Jordan.FromJSON.Class

Methods

gFromJSONTuple :: JSONTupleParser f => FromJSONOptions -> f ((lhs :*: rhs) a) Source #

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

Defined in Jordan.FromJSON.Class

Methods

gFromJSONTuple :: JSONTupleParser f0 => FromJSONOptions -> f0 (S1 ('MetaSel 'Nothing su ss ds) f a) Source #