aeson-schemas-1.3.1: Easily consume JSON data on-demand with type-safety

MaintainerBrandon Chinn <brandon@leapyear.io>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Data.Aeson.Schema

Contents

Description

This module defines a new way of parsing JSON data by defining type-level schemas and extracting information using quasiquoters that will check if a given query path is valid at compile-time.

Synopsis

Object

data Object (schema :: Schema) Source #

The object containing JSON data and its schema.

Has a FromJSON instance, so you can use the usual Data.Aeson decoding functions.

obj = decode "{\"a\": 1}" :: Maybe (Object [schema| { a: Int } |])
Instances
IsSchema schema => Eq (Object schema) Source # 
Instance details

Defined in Data.Aeson.Schema.Internal

Methods

(==) :: Object schema -> Object schema -> Bool #

(/=) :: Object schema -> Object schema -> Bool #

IsSchema schema => Show (Object schema) Source # 
Instance details

Defined in Data.Aeson.Schema.Internal

Methods

showsPrec :: Int -> Object schema -> ShowS #

show :: Object schema -> String #

showList :: [Object schema] -> ShowS #

IsSchema schema => ToJSON (Object schema) Source # 
Instance details

Defined in Data.Aeson.Schema.Internal

Methods

toJSON :: Object schema -> Value #

toEncoding :: Object schema -> Encoding #

toJSONList :: [Object schema] -> Value #

toEncodingList :: [Object schema] -> Encoding #

IsSchema schema => FromJSON (Object schema) Source # 
Instance details

Defined in Data.Aeson.Schema.Internal

Methods

parseJSON :: Value -> Parser (Object schema) #

parseJSONList :: Value -> Parser [Object schema] #

toMap :: IsSchema (Schema schema) => Object (Schema schema) -> Object Source #

Convert an Object into a HashMap, losing the type information in the schema.

Since: 1.3.0

Schemas

type Schema = Schema' Symbol Type Source #

The kind of schemas that may be used with Object; e.g.

data Payload (schema :: Schema) = Payload
  { getPayload :: Object schema
  , timestamp  :: UTCTime
  }

type IsSchema (schema :: Schema) = (HasSchemaResult (ToSchemaObject schema), All HasSchemaResultPair (FromSchema schema), SchemaResult (ToSchemaObject schema) ~ Object schema) Source #

The constraint for most operations involving Object schema. If you're writing functions on general Objects, you should use this constraint. e.g.

logObject :: (MonadLogger m, IsSchema schema) => Object schema -> m ()
logObject = logInfoN . Text.pack . show

Since: 1.3.0

showSchema :: forall (schema :: Schema). IsSchema schema => String Source #

Show the given schema.

Usage:

type MySchema = [schema| { a: Int } |]
showSchema @MySchema

Quasiquoters for extracting or manipulating JSON data or schemas

schema :: QuasiQuoter Source #

Defines a QuasiQuoter for writing schemas.

Example:

import Data.Aeson.Schema (schema)

type MySchema = [schema|
  {
    foo: {
      a: Int,
      // you can add comments like this
      nodes: List {
        b: Maybe Bool,
      },
      c: Text,
      d: Text,
      e: MyType,
      f: Maybe List {
        name: Text,
      },
    },
  }
|]

Syntax:

  • { key: <schema>, ... } corresponds to a JSON Object with the given key mapping to the given schema.
  • Bool, Int, Double, and Text correspond to the usual Haskell values.
  • Maybe <schema> and List <schema> correspond to Maybe and [], containing values specified by the provided schema (no parentheses needed).
  • Try <schema> corresponds to Maybe, where the value will be Just if the given schema successfully parses the value, or Nothing otherwise. Different from Maybe <schema>, where parsing { "foo": true } with { foo: Try Int } returns Nothing, whereas it would be a parse error with { foo: Maybe Int } (added in v1.2.0)
  • Any other uppercase identifier corresponds to the respective type in scope -- requires a FromJSON instance.

Advanced syntax:

  • <schema1> | <schema2> corresponds to a JSON value that matches one of the given schemas. When extracted from an Object, it deserializes into a JSONSum object. (added in v1.1.0)
  • { [key]: <schema> } uses the current object to resolve the keys in the given schema. Only object schemas are allowed here. (added in v1.2.0)
  • { key: #Other, ... } maps the given key to the Other schema. The Other schema needs to be defined in another module.
  • { #Other, ... } extends this schema with the Other schema. The Other schema needs to be defined in another module.

get :: QuasiQuoter Source #

Defines a QuasiQuoter for extracting JSON data.

Example:

let Just result = decode ... :: Maybe (Object MySchema)

[get| result.foo.a |]          :: Int
[get| result.foo.nodes |]      :: [Object (..)]
[get| result.foo.nodes[] |]    :: [Object (..)]
[get| result.foo.nodes[].b |]  :: [Maybe Bool]
[get| result.foo.nodes[].b! |] :: [Bool] -- runtime error if any values are Nothing
[get| result.foo.c |]          :: Text
[get| result.foo.(a,c) |]      :: (Int, Text)
[get| result.foo.[c,d] |]      :: [Text]

let nodes = [get| result.foo.nodes |]
flip map nodes $ \node -> fromMaybe ([get| node.num |] == 0) [get| node.b |]
map [get| .num |] nodes

Syntax:

  • x.y is only valid if x is an Object. Returns the value of the key y.
  • .y returns a function that takes in an Object and returns the value of the key y.
  • x.[y,z.a] is only valid if x is an Object, and if y and z.a have the same type. Returns the value of the operations y and z.a as a list. MUST be the last operation.
  • x.(y,z.a) is only valid if x is an Object. Returns the value of the operations y and z.a as a tuple. MUST be the last operation.
  • x! is only valid if x is a Maybe. Unwraps the value of x from a Just value and errors (at runtime!) if x is Nothing.
  • x[] is only valid if x is a list. Applies the remaining rules as an fmap over the values in the list, e.g.

    • x[] without anything after is equivalent to x
    • x[].y gets the key y in all the Objects in x
    • x[]! unwraps all Just values in x (and errors if any Nothing values exist in x)
  • x? follows the same rules as x[] except it's only valid if x is a Maybe.
  • x@# is only valid if x is a SumType. If the sum type contains a value at the given branch (e.g. x@0 for Here v), return Just that value, otherwise Nothing. (added in v1.1.0)

e.g. with the schema { a: Int | Bool }, calling [get| .a@0 |] will return Maybe Int if the sum type contains an Int.

unwrap :: QuasiQuoter Source #

Defines a QuasiQuoter to extract a schema within the given schema.

The base schema needs to be defined in a separate module.

For example:

-- | MyFoo ~ Object [schema| { b: Maybe Bool } |]
type MyFoo = [unwrap| MySchema.foo.nodes[] |]

If the schema is imported qualified, you can use parentheses to distinguish it from the expression:

type MyFoo = [unwrap| (MyModule.Schema).foo.nodes[] |]

You can then use the type alias as usual:

parseBar :: MyFoo -> String
parseBar = maybe "null" show . [get| .b |]

foo = map parseBar [get| result.foo.nodes[] |]

The syntax is mostly the same as get, except the operations run on the type itself, instead of the values. Differences from get:

  • x! is only valid if x is a Maybe a type. Returns a, the type wrapped in the Maybe.
  • x? is the same as x!.
  • x[] is only valid if x is a [a] type. Returns a, the type contained in the list.
  • x@# is only valid if x is a SumType. Returns the type at that branch in the sum type.

mkGetter :: String -> String -> Name -> String -> DecsQ Source #

A helper that generates a get expression and a type alias for the result of the expression.

mkGetter "Node" "getNodes" ''MySchema ".nodes[]"

{- is equivalent to -}

-- | Node ~ { b: Maybe Bool }
type Node = [unwrap| MySchema.nodes[] |]

getNodes :: Object MySchema -> [Node]
getNodes = [get| .nodes[] |]

mkGetter takes four arguments:

unwrapName
The name of the type synonym to store the unwrapped schema as
funcName
The name of the getter function
startSchema
The schema to extract/unwrap from
ops
The operation to pass to the get and unwrap quasiquoters

There is one subtlety that occurs from the use of the same ops string for both the unwrap and get quasiquoters: unwrap strips out intermediate functors, while get applies within the functor. So in the above example, ".nodes[]" strips out the list when saving the schema to Node, while in the below example, ".nodes" doesn't strip out the list when saving the schema to Nodes.

mkGetter "Nodes" "getNodes" ''MySchema ".nodes"

{- is equivalent to -}

-- | Nodes ~ List { b: Maybe Bool }
type Nodes = [unwrap| MySchema.nodes |]

getNodes :: Object MySchema -> Nodes
getNodes = [get| .nodes |]

As another example,

mkGetter "MyName" "getMyName" ''MySchema ".f?[].name"

{- is equivalent to -}

-- | MyName ~ Text
type MyName = [unwrap| MySchema.f?[].name |]

getMyBool :: Object MySchema -> Maybe [MyName]
getMyBool = [get| .f?[].name |]