| Maintainer | Brandon Chinn <brandonchinn178@gmail.com> |
|---|---|
| Stability | experimental |
| Portability | portable |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Data.Aeson.Schema
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
- data Object (schema :: Schema)
- toMap :: IsSchema ('Schema schema) => Object ('Schema schema) -> Object
- type Schema = Schema' Symbol Type
- type IsSchema (schema :: Schema) = (HasSchemaResult (ToSchemaObject schema), All HasSchemaResultPair (FromSchema schema), IsSchemaObjectMap (FromSchema schema), SchemaResult (ToSchemaObject schema) ~ Object schema)
- showSchema :: forall (schema :: Schema). IsSchema schema => String
- schema :: QuasiQuoter
- get :: QuasiQuoter
- unwrap :: QuasiQuoter
- mkGetter :: String -> String -> Name -> String -> DecsQ
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 } |])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), IsSchemaObjectMap (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 @MySchemaQuasiquoters 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 JSONObjectwith the given key mapping to the given schema.Bool,Int,Double, andTextcorrespond to the usual Haskell values.Maybe <schema>andList <schema>correspond toMaybeand[], containing values specified by the provided schema (no parentheses needed).Try <schema>corresponds toMaybe, where the value will beJustif the given schema successfully parses the value, orNothingotherwise. Different fromMaybe <schema>, where parsing{ "foo": true }with{ foo: Try Int }returnsNothing, 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 anObject, it deserializes into aJSONSumobject. (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 theOtherschema. TheOtherschema needs to be defined in another module.{ #Other, ... }extends this schema with theOtherschema. TheOtherschema 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.yis only valid ifxis anObject. Returns the value of the keyy..yreturns a function that takes in anObjectand returns the value of the keyy.x.[y,z.a]is only valid ifxis anObject, and ifyandz.ahave the same type. Returns the value of the operationsyandz.aas a list. MUST be the last operation.x.(y,z.a)is only valid ifxis anObject. Returns the value of the operationsyandz.aas a tuple. MUST be the last operation.x!is only valid ifxis aMaybe. Unwraps the value ofxfrom aJustvalue and errors (at runtime!) ifxisNothing.x[]is only valid ifxis a list. Applies the remaining rules as anfmapover the values in the list, e.g.x?follows the same rules asx[]except it's only valid ifxis aMaybe.x@#is only valid ifxis aSumType. If the sum type contains a value at the given branch (e.g.x@0forHere v), returnJustthat value, otherwiseNothing. (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 ifxis aMaybe atype. Returnsa, the type wrapped in theMaybe.x?is the same asx!.x[]is only valid ifxis a[a]type. Returnsa, the type contained in the list.x@#is only valid ifxis aSumType. 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
getandunwrapquasiquoters
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 |]