JsonGrammar-0.2: Combinators for bidirectional JSON parsing

Language.JsonGrammar

Contents

Synopsis

Constructing JSON grammars

liftAeson :: (FromJSON a, ToJSON a) => Iso (Value :- t) (a :- t)Source

Convert any Aeson-enabled type to a grammar.

option :: Iso (Value :- t) (a :- t) -> Iso (Value :- t) (Maybe a :- t)Source

Introduce Null as possible value. First gives the argument grammar a chance, only yielding Null or Nothing if the argument grammar fails to handle the input.

greedyOption :: Iso (Value :- t) (a :- t) -> Iso (Value :- t) (Maybe a :- t)Source

Introduce Null as possible (greedy) value. Always converts Nothing to Null and vice versa, even if the argument grammar knows how to handle these values.

list :: Iso (Value :- t) (a :- t) -> Iso (Value :- t) ([a] :- t)Source

Convert between a JSON array and Haskell list of arbitrary lengts. The elements are converted using the argument grammar.

elementBy :: Iso (Value :- t) (a :- t) -> Iso ([Value] :- t) ([Value] :- (a :- t))Source

Describe a single array element with the given grammar.

array :: Iso ([Value] :- t1) ([Value] :- t2) -> Iso (Value :- t1) t2Source

Wrap a bunch of elements in a JSON array. For example, to match an array of exactly length two:

 array (element . element)

Or to match an empty array:

 array id

propBy :: Iso (Value :- t) (a :- t) -> String -> Iso (Object :- t) (Object :- (a :- t))Source

Describe a property with the given name and value grammar.

rawFixedProp :: String -> Value -> Iso (Object :- t) (Object :- t)Source

Expect a specific key/value pair.

rest :: Iso (Object :- t) (Object :- (Map Text Value :- t))Source

Collect all properties left in an object.

ignoreRest :: Iso (Object :- t) (Object :- t)Source

Match and discard all properties left in the object. When converting back to JSON, produces no properties.

object :: Iso (Object :- t1) (Object :- t2) -> Iso (Value :- t1) t2Source

Wrap an exhaustive bunch of properties in an object. Typical usage:

 object (prop "key1" . prop "key2")

Type-directed conversion

class Json a whereSource

Convert values of a type to and from JSON.

Methods

grammar :: Iso (Value :- t) (a :- t)Source

Instances

Json Bool 
Json Double 
Json Float 
Json Int 
Json Integer 
Json Value 
Json [Char] 
Json a => Json [a] 
Json a => Json (Maybe a) 
(Json a, Json b) => Json (Either a b) 

fromJson :: Json a => Value -> Maybe aSource

Convert from JSON.

toJson :: Json a => a -> Maybe ValueSource

Convert to JSON.

litJson :: Json a => a -> Iso (Value :- t) tSource

Expect/produce a specific JSON Value.

prop :: Json a => String -> Iso (Object :- t) (Object :- (a :- t))Source

Describe a property whose value grammar is described by a Json instance.

fixedProp :: Json a => String -> a -> Iso (Object :- t) (Object :- t)Source

Expect a specific key/value pair.

element :: Json a => Iso ([Value] :- t) ([Value] :- (a :- t))Source

Describe a single array element whose grammar is given by a Json instance.