| Maintainer | Brandon Chinn <brandon@leapyear.io> |
|---|---|
| Stability | experimental |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Aeson.Schema.TH
Contents
Description
Template Haskell definitions for doing various aeson-schemas operations.
SchemaType defines the shape of the JSON object stored in
Object, and we can use getKey to lookup a key that
is checked at compile-time to exist in the object.
To make it easier to extract deeply nested keys, this module defines QuasiQuoters that generate the
corresponding getKey expressions.
In addition to the QuasiQuotes extension, the following extensions will need to be enabled to use these QuasiQuoters:
- DataKinds
- FlexibleContexts
- TypeFamilies
Documentation
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).- Any other uppercase identifier corresponds to the respective type in scope -- requires a FromJSON instance.
{ key: #Other, ... }maps the given key to theOtherschema.{ #Other, ... }extends this schema with theOtherschema.
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.
unwrap :: QuasiQuoter Source #
Defines a QuasiQuoter to extract a schema within the given schema.
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.
Utilities
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:
type Node = [unwrap| MySchema.nodes[] |] -- Object [schema| { b: Maybe Bool } |]
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:
type Nodes = [unwrap| MySchema.nodes! |] -- [Object [schema| { b: Maybe Bool } |]]
getNodes :: Object MySchema -> Nodes
getNodes = [get| .nodes! |]As another example,
mkGetter "MyName" "getMyName" ''MySchema ".f?[].name" -- is equivalent to: type MyName = [unwrap| MySchema.f?[].name |] -- Text getMyBool :: Object MySchema -> Maybe [MyName] getMyBool = [get| .f?[].name |]
Helpers for Enum types
mkEnum :: String -> [String] -> Q [Dec] Source #
Make an enum type with the given constructors, that can be parsed from JSON.
The FromJSON instance will match to a string value matching the constructor name,
case-insensitive.
mkEnum State [OPEN, CLOSED] main = print [ decode "open" :: Maybe State , decode "OPEN" :: Maybe State , decode "closed" :: Maybe State , decode "CLOSED" :: Maybe State ]
genFromJSONEnum :: Name -> Q [Dec] Source #
Generate an instance of FromJSON for the given data type.
Prefer using mkEnum; this function is useful for data types in which you want greater control
over the actual data type.
The FromJSON instance will match to a string value matching the constructor name,
case-insensitive.
data State = OPEN | CLOSED deriving (Show,Enum) genFromJSONEnum ''State main = print [ decode "open" :: Maybe State , decode "OPEN" :: Maybe State , decode "closed" :: Maybe State , decode "CLOSED" :: Maybe State ]