aeson-quick-0.2.0: Quick JSON extractions with Aeson

Safe HaskellNone
LanguageHaskell2010

Data.Aeson.Quick

Synopsis

Documentation

aeson-quick is a library for terse marshalling of data to and from aeson's Value.

It works on the observation that by turning objects into tuples inside the Value, the type system can be employed to do more of the work.

For example, given the JSON:

{ "name": "bob"
, "age": 29
, "hobbies": [{"name": "tennis"}, {"name": "cooking"}]
}

You can write:

extractHobbyist :: Value -> Maybe (Value, Int, [Value])
extractHobbyist = (.? "{name,age,hobbies:[{name}]}")

module Data.Aeson

(.?) :: FromJSON a => Value -> Quick -> Maybe a Source #

Extracts instances of FromJSON from a Value

This is a wrapper around extract which does the actual work.

Examples assume FromJSON Foo and FromJSON Bar.

Extract key from object:

>>> value .? "{key}" :: Maybe Foo

Extract list of objects:

>>> value .? "[{key}]" :: Maybe [Foo]

Extract with optional key:

>>> value .? "{key,opt?}" :: Maybe (Foo, Maybe Bar)

(.!) :: FromJSON a => Value -> Quick -> a Source #

Unsafe version of .?. Returns error on failure.

extract :: FromJSON a => Quick -> Value -> Parser a Source #

The Parser that executes a Quick against a Value to return an instance of FromJSON.

(.%) :: ToJSON a => Quick -> a -> Value Source #

Turns data into JSON objects.

This is a wrapper around build which does the actual work.

Build a simple Value:

>>> encode $ "{a}" .% True
{\"a\": True}

Build a complex Value:

>>> encode $ "[{a}]" '.%' [True, False]
"[{\"a\":true},{\"a\":false}]"

build :: ToJSON a => Quick -> a -> Either String Value Source #

Executes a Quick against provided data to update a Value.

data Quick Source #

Constructors

Obj [(KeyType, Bool, Quick)] 
Arr Quick Bounds 
Val 
Instances
Eq Quick Source # 
Instance details

Defined in Data.Aeson.Quick

Methods

(==) :: Quick -> Quick -> Bool #

(/=) :: Quick -> Quick -> Bool #

Ord Quick Source # 
Instance details

Defined in Data.Aeson.Quick

Methods

compare :: Quick -> Quick -> Ordering #

(<) :: Quick -> Quick -> Bool #

(<=) :: Quick -> Quick -> Bool #

(>) :: Quick -> Quick -> Bool #

(>=) :: Quick -> Quick -> Bool #

max :: Quick -> Quick -> Quick #

min :: Quick -> Quick -> Quick #

Show Quick Source # 
Instance details

Defined in Data.Aeson.Quick

Methods

showsPrec :: Int -> Quick -> ShowS #

show :: Quick -> String #

showList :: [Quick] -> ShowS #

IsString Quick Source # 
Instance details

Defined in Data.Aeson.Quick

Methods

fromString :: String -> Quick

Generic Quick Source # 
Instance details

Defined in Data.Aeson.Quick

Associated Types

type Rep Quick :: Type -> Type

Methods

from :: Quick -> Rep Quick x

to :: Rep Quick x -> Quick

NFData Quick Source # 
Instance details

Defined in Data.Aeson.Quick

Methods

rnf :: Quick -> ()

type Rep Quick Source # 
Instance details

Defined in Data.Aeson.Quick

type Rep Quick

parseQuick :: Text -> Either String Quick Source #

Parse a structure, can fail

quick :: QuasiQuoter Source #

QuasiQuoter for a structure, provides compile time checking ie:

>>> val .! [quick|{foo,bar}|]

jsonlit :: QuasiQuoter Source #