jordan-0.1.0.0: JSON with Structure
Safe HaskellSafe-Inferred
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 => JSONObjectParser f where Source #

A class for parsing JSON objects.

Minimal complete definition

parseFieldWith

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!

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

Instances

Instances details
JSONObjectParser ObjectParser Source # 
Instance details

Defined in Jordan.FromJSON.Megaparsec

Methods

parseFieldWith :: Text -> (forall (valueParser :: Type -> Type). JSONParser valueParser => valueParser a) -> ObjectParser a Source #

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

class Applicative 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.

Instances

Instances details
JSONTupleParser ArrayParser Source # 
Instance details

Defined in Jordan.FromJSON.Megaparsec

Methods

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

consumeItem :: FromJSON v => ArrayParser v Source #

class (Functor f, forall a. Monoid (f a)) => 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

:: Text

A label for the object. This label should, as much as possible, be "globally unique" in some way. This will enable better generation of documentation.

-> (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 :: Text -> (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 #

parseNull :: f () Source #

parseBool :: f Bool Source #

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

Instances

Instances details
JSONParser MegaparsecParser Source # 
Instance details

Defined in Jordan.FromJSON.Megaparsec

Methods

parseObject :: Text -> (forall (objectParser :: Type -> Type). JSONObjectParser objectParser => objectParser a) -> MegaparsecParser a Source #

parseObjectStrict :: Text -> (forall (objectParser :: Type -> Type). JSONObjectParser objectParser => objectParser a) -> MegaparsecParser a Source #

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

parseText :: MegaparsecParser Text Source #

parseTextConstant :: Text -> MegaparsecParser () Source #

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

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

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

parseNumber :: MegaparsecParser Scientific Source #

parseNull :: MegaparsecParser () Source #

parseBool :: MegaparsecParser Bool Source #

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

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.

Minimal complete definition

Nothing

Methods

fromJSON :: JSONParser f => f value Source #

default fromJSON :: (Generic value, GFromJSON (Rep 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 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 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, Typeable 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, 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 Text a) Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f (Map Text 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.1.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)))))

class GFromJSON v where Source #

Methods

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

Instances

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

Defined in Jordan.FromJSON.Class

Methods

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

(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 # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

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

Constructor t => GFromJSON (PartOfSum (C1 t (U1 :: Type -> Type))) Source # 
Instance details

Defined in Jordan.FromJSON.Class

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

Defined in Jordan.FromJSON.Class

Methods

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

(Constructor t, Constructor t') => GFromJSON (C1 t (U1 :: Type -> Type) :+: C1 t' (U1 :: Type -> Type)) Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

gFromJSON :: JSONParser f => FromJSONOptions -> f ((C1 t U1 :+: C1 t' U1) a) Source #

(GFromJSON (PartOfSum l), GFromJSON (PartOfSum r)) => GFromJSON (l :+: r) Source # 
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 # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

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

Constructor t => GFromJSON (C1 t (U1 :: Type -> Type)) Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

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

FromJSON s => GFromJSON (C1 c (S1 ('MetaSel ('Nothing :: Maybe Symbol) su ss ds) (Rec0 s))) Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

gFromJSON :: JSONParser f => FromJSONOptions -> f (C1 c (S1 ('MetaSel 'Nothing su ss ds) (Rec0 s)) a) Source #

(GFromJSONObject i, Constructor c) => GFromJSON (C1 c i) Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

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

class GFromJSONObject v where Source #

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 c :: Type -> Type)) Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

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