Copyright | (c) Aaron Allen 2020 |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Aaron Allen <aaronallen8455@gmail.com> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Typson.JsonTree
Description
Synopsis
- class FieldSYM repr => ObjectSYM (repr :: Tree -> Type -> Type) where
- object :: (tree ~ 'Node 'Product edges, NoDuplicateKeys o edges) => String -> TreeBuilder (Field repr o) tree o -> repr tree o
- prim :: (FromJSON v, ToJSON v) => repr 'Leaf v
- list :: repr tree o -> repr ('IndexedNode Nat tree) [o]
- textMap :: (FromJSONKey k, ToJSONKey k, IsString k, Ord k) => repr tree o -> repr ('IndexedNode Symbol tree) (Map k o)
- set :: Ord o => repr tree o -> repr ('IndexedNode Nat tree) (Set o)
- vector :: repr tree o -> repr ('IndexedNode Nat tree) (Vector o)
- class FieldSYM repr where
- data Field repr :: Type -> Tree -> Type -> Type
- field :: (KnownSymbol key, edge ~ 'Edge key 'Singleton field subTree, tree ~ 'Node 'Product '[edge]) => proxy key -> (obj -> field) -> repr subTree field -> Field repr obj tree field
- optField :: (KnownSymbol key, edge ~ 'Edge key 'Nullable field subTree, tree ~ 'Node 'Product '[edge]) => proxy key -> (obj -> Maybe field) -> repr subTree field -> Field repr obj tree (Maybe field)
- optFieldDef :: (KnownSymbol key, edge ~ 'Edge key 'Singleton field subTree, tree ~ 'Node 'Product '[edge]) => proxy key -> (obj -> field) -> field -> repr subTree field -> Field repr obj tree field
- class UnionSYM (repr :: Tree -> Type -> Type) where
- type Result repr union :: Type
- data Tag repr :: Type -> Tree -> Type -> Type
- union :: (tree ~ 'Node 'Sum edges, NoDuplicateKeys union edges) => String -> TreeBuilder (Tag repr union) tree (union -> Result repr union) -> repr tree union
- tag :: (KnownSymbol name, edge ~ 'Edge name 'Nullable v subTree, tree ~ 'Node 'Sum '[edge]) => proxy name -> (v -> union) -> repr subTree v -> Tag repr union tree (v -> Result repr union)
- type JsonSchema t a = forall repr. (ObjectSYM repr, UnionSYM repr) => repr t a
- key :: Proxy (key :: Symbol)
- newtype ObjectEncoder (t :: Tree) o = ObjectEncoder {
- encodeObject :: o -> Value
- newtype ObjectDecoder (t :: Tree) o = ObjectDecoder {
- decodeObject :: Value -> Parser o
- newtype ObjectTree (t :: Tree) o = ObjectTree {
- getObjectTree :: TreeProxy t o
- data TreeBuilder (f :: Tree -> Type -> Type) (t :: Tree) (a :: Type)
- (<<$>) :: (a -> b) -> f ('Node aggr '[edge]) a -> TreeBuilder f ('Node aggr '[edge]) b
- (<<*>) :: TreeBuilder f ('Node aggr edges) (a -> b) -> f ('Node aggr '[edge]) a -> TreeBuilder f ('Node aggr (edge ': edges)) b
- runAp :: Applicative g => (forall a' t'. f t' a' -> g a') -> TreeBuilder f t a -> g a
- runAp_ :: Monoid m => (forall a' t'. f t' a' -> m) -> TreeBuilder f t a -> m
- data Tree
- = Node Aggregator [Edge]
- | IndexedNode Type Tree
- | Leaf
- data Edge = Edge Symbol Multiplicity Type Tree
- data Aggregator
- data Multiplicity
- type family NoDuplicateKeys (obj :: Type) (edges :: [Edge]) :: Constraint where ...
Schema Semantics
Type classes and type-level data structures for representing the JSON structure of data.
Defining JSON Schemas
class FieldSYM repr => ObjectSYM (repr :: Tree -> Type -> Type) where Source #
Used to interpret JSON trees for haskell record types.
Methods
Arguments
:: (tree ~ 'Node 'Product edges, NoDuplicateKeys o edges) | |
=> String | Name of the object as it will appear in parse errors |
-> TreeBuilder (Field repr o) tree o | The collection of fields |
-> repr tree o |
Declares the schema for a record type.
data Person = Person { name :: Text , age :: Int } personJ :: JsonSchema _ Person personJ = object "Person" $ Person <<$> field (key @"name") name prim <<*> field (key @"age") age prim
prim :: (FromJSON v, ToJSON v) => repr 'Leaf v Source #
Serves as a schema for a type that cannot itself be broken down into
named fields. The type must have FromJSON
and ToJSON
instances.
Arguments
:: repr tree o | Element schema |
-> repr ('IndexedNode Nat tree) [o] |
Given a schema for some type a
, create a schema for [a]
.
This will allow you to write queries specifying an index into the list:
type ListQuery = "foo" :-> "bar" :-> 3 :-> "baz"
Arguments
:: (FromJSONKey k, ToJSONKey k, IsString k, Ord k) | |
=> repr tree o | Element schema |
-> repr ('IndexedNode Symbol tree) (Map k o) |
Produces a schema for a Map
given a schema for it's elements type. The
key of the map should be some sort of string.
You can have arbitrary keys when constructing a query path into a textMap
schema.
Arguments
:: Ord o | |
=> repr tree o | Element schema |
-> repr ('IndexedNode Nat tree) (Set o) |
Construct a Set
schema given a schema for it's elements.
Arguments
:: repr tree o | Element schema |
-> repr ('IndexedNode Nat tree) (Vector o) |
Construct a Vector
schema given a schema for it's elements.
Instances
class FieldSYM repr where Source #
Methods
Arguments
:: (KnownSymbol key, edge ~ 'Edge key 'Singleton field subTree, tree ~ 'Node 'Product '[edge]) | |
=> proxy key | The |
-> (obj -> field) | The accessor for the field |
-> repr subTree field | Schema for the type of the field |
-> Field repr obj tree field |
Defines a required field
Arguments
:: (KnownSymbol key, edge ~ 'Edge key 'Nullable field subTree, tree ~ 'Node 'Product '[edge]) | |
=> proxy key | The |
-> (obj -> Maybe field) | The accessor for the field |
-> repr subTree field | Schema for the type of the field |
-> Field repr obj tree (Maybe field) |
Defines an optional field. Will parse Nothing
for either a null
JSON
value or if the key is missing. Will encode Nothing
as null
.
Arguments
:: (KnownSymbol key, edge ~ 'Edge key 'Singleton field subTree, tree ~ 'Node 'Product '[edge]) | |
=> proxy key | The |
-> (obj -> field) | The accessor for the field |
-> field | Default value to emit |
-> repr subTree field | Schema for the type of the field |
-> Field repr obj tree field |
Defines an optional field where parsing will emit the given default value
if the field is null
or the key is absent.
Instances
FieldSYM ObjectDecoder Source # | |
Defined in Typson.JsonTree Methods field :: forall (key :: Symbol) (edge :: Edge) field (subTree :: Tree) (tree :: Tree) proxy obj. (KnownSymbol key, edge ~ 'Edge key 'Singleton field subTree, tree ~ 'Node 'Product '[edge]) => proxy key -> (obj -> field) -> ObjectDecoder subTree field -> Field ObjectDecoder obj tree field Source # optField :: forall (key :: Symbol) (edge :: Edge) field (subTree :: Tree) (tree :: Tree) proxy obj. (KnownSymbol key, edge ~ 'Edge key 'Nullable field subTree, tree ~ 'Node 'Product '[edge]) => proxy key -> (obj -> Maybe field) -> ObjectDecoder subTree field -> Field ObjectDecoder obj tree (Maybe field) Source # optFieldDef :: forall (key :: Symbol) (edge :: Edge) field (subTree :: Tree) (tree :: Tree) proxy obj. (KnownSymbol key, edge ~ 'Edge key 'Singleton field subTree, tree ~ 'Node 'Product '[edge]) => proxy key -> (obj -> field) -> field -> ObjectDecoder subTree field -> Field ObjectDecoder obj tree field Source # | |
FieldSYM ObjectEncoder Source # | |
Defined in Typson.JsonTree Methods field :: forall (key :: Symbol) (edge :: Edge) field (subTree :: Tree) (tree :: Tree) proxy obj. (KnownSymbol key, edge ~ 'Edge key 'Singleton field subTree, tree ~ 'Node 'Product '[edge]) => proxy key -> (obj -> field) -> ObjectEncoder subTree field -> Field ObjectEncoder obj tree field Source # optField :: forall (key :: Symbol) (edge :: Edge) field (subTree :: Tree) (tree :: Tree) proxy obj. (KnownSymbol key, edge ~ 'Edge key 'Nullable field subTree, tree ~ 'Node 'Product '[edge]) => proxy key -> (obj -> Maybe field) -> ObjectEncoder subTree field -> Field ObjectEncoder obj tree (Maybe field) Source # optFieldDef :: forall (key :: Symbol) (edge :: Edge) field (subTree :: Tree) (tree :: Tree) proxy obj. (KnownSymbol key, edge ~ 'Edge key 'Singleton field subTree, tree ~ 'Node 'Product '[edge]) => proxy key -> (obj -> field) -> field -> ObjectEncoder subTree field -> Field ObjectEncoder obj tree field Source # | |
FieldSYM ObjectTree Source # | |
Defined in Typson.JsonTree Methods field :: forall (key :: Symbol) (edge :: Edge) field (subTree :: Tree) (tree :: Tree) proxy obj. (KnownSymbol key, edge ~ 'Edge key 'Singleton field subTree, tree ~ 'Node 'Product '[edge]) => proxy key -> (obj -> field) -> ObjectTree subTree field -> Field ObjectTree obj tree field Source # optField :: forall (key :: Symbol) (edge :: Edge) field (subTree :: Tree) (tree :: Tree) proxy obj. (KnownSymbol key, edge ~ 'Edge key 'Nullable field subTree, tree ~ 'Node 'Product '[edge]) => proxy key -> (obj -> Maybe field) -> ObjectTree subTree field -> Field ObjectTree obj tree (Maybe field) Source # optFieldDef :: forall (key :: Symbol) (edge :: Edge) field (subTree :: Tree) (tree :: Tree) proxy obj. (KnownSymbol key, edge ~ 'Edge key 'Singleton field subTree, tree ~ 'Node 'Product '[edge]) => proxy key -> (obj -> field) -> field -> ObjectTree subTree field -> Field ObjectTree obj tree field Source # |
class UnionSYM (repr :: Tree -> Type -> Type) where Source #
Used to interpret JSON trees for haskell sum types.
Methods
Arguments
:: (tree ~ 'Node 'Sum edges, NoDuplicateKeys union edges) | |
=> String | Name of the union as it will appear in parse errors |
-> TreeBuilder (Tag repr union) tree (union -> Result repr union) | A collection of tags, one for each branch of the union |
-> repr tree union |
Declares a schema for a tagged sum type
data Classifier = Flora Plant | Fauna Animal classifierJ :: JsonSchema _ Classifier classifierJ = union "Classifier" $ classifierTags <<$> tag (key @"flora") Flora plantJ <<*> tag (key @"fauna") Fauna animalJ
The resulting JSON is an object with a single field with a key/value pair corresponding to one of the branches of the sum type.
Arguments
:: (KnownSymbol name, edge ~ 'Edge name 'Nullable v subTree, tree ~ 'Node 'Sum '[edge]) | |
=> proxy name |
|
-> (v -> union) | Data constructor |
-> repr subTree v | Schema for the value that this branch tags |
-> Tag repr union tree (v -> Result repr union) |
Used to declare a single branch of a sum type. The constructor for the branch should take a single argument. If you require more than one argument then you should package them up into a separate record type.
Instances
UnionSYM ObjectDecoder Source # | |
Defined in Typson.JsonTree Associated Types type Result ObjectDecoder union Source # data Tag ObjectDecoder :: Type -> Tree -> Type -> Type Source # Methods union :: forall (tree :: Tree) (edges :: [Edge]) union. (tree ~ 'Node 'Sum edges, NoDuplicateKeys union edges) => String -> TreeBuilder (Tag ObjectDecoder union) tree (union -> Result ObjectDecoder union) -> ObjectDecoder tree union Source # tag :: forall (name :: Symbol) (edge :: Edge) v (subTree :: Tree) (tree :: Tree) proxy union. (KnownSymbol name, edge ~ 'Edge name 'Nullable v subTree, tree ~ 'Node 'Sum '[edge]) => proxy name -> (v -> union) -> ObjectDecoder subTree v -> Tag ObjectDecoder union tree (v -> Result ObjectDecoder union) Source # | |
UnionSYM ObjectEncoder Source # | |
Defined in Typson.JsonTree Associated Types type Result ObjectEncoder union Source # data Tag ObjectEncoder :: Type -> Tree -> Type -> Type Source # Methods union :: forall (tree :: Tree) (edges :: [Edge]) union. (tree ~ 'Node 'Sum edges, NoDuplicateKeys union edges) => String -> TreeBuilder (Tag ObjectEncoder union) tree (union -> Result ObjectEncoder union) -> ObjectEncoder tree union Source # tag :: forall (name :: Symbol) (edge :: Edge) v (subTree :: Tree) (tree :: Tree) proxy union. (KnownSymbol name, edge ~ 'Edge name 'Nullable v subTree, tree ~ 'Node 'Sum '[edge]) => proxy name -> (v -> union) -> ObjectEncoder subTree v -> Tag ObjectEncoder union tree (v -> Result ObjectEncoder union) Source # | |
UnionSYM ObjectTree Source # | |
Defined in Typson.JsonTree Associated Types type Result ObjectTree union Source # data Tag ObjectTree :: Type -> Tree -> Type -> Type Source # Methods union :: forall (tree :: Tree) (edges :: [Edge]) union. (tree ~ 'Node 'Sum edges, NoDuplicateKeys union edges) => String -> TreeBuilder (Tag ObjectTree union) tree (union -> Result ObjectTree union) -> ObjectTree tree union Source # tag :: forall (name :: Symbol) (edge :: Edge) v (subTree :: Tree) (tree :: Tree) proxy union. (KnownSymbol name, edge ~ 'Edge name 'Nullable v subTree, tree ~ 'Node 'Sum '[edge]) => proxy name -> (v -> union) -> ObjectTree subTree v -> Tag ObjectTree union tree (v -> Result ObjectTree union) Source # |
type JsonSchema t a = forall repr. (ObjectSYM repr, UnionSYM repr) => repr t a Source #
A rank-N type synonym used in the type signature of JSON schemas
Core Interpreters
A single schema can be interpreted in different ways. This allows it to be used as both an encoder and decoder. Because the schema semantics are using the final tagless style, users are able to write their own interpreters.
newtype ObjectEncoder (t :: Tree) o Source #
Use a Tree
to encode a type as an Aeson Value
Constructors
ObjectEncoder | |
Fields
|
Instances
UnionSYM ObjectEncoder Source # | |
Defined in Typson.JsonTree Associated Types type Result ObjectEncoder union Source # data Tag ObjectEncoder :: Type -> Tree -> Type -> Type Source # Methods union :: forall (tree :: Tree) (edges :: [Edge]) union. (tree ~ 'Node 'Sum edges, NoDuplicateKeys union edges) => String -> TreeBuilder (Tag ObjectEncoder union) tree (union -> Result ObjectEncoder union) -> ObjectEncoder tree union Source # tag :: forall (name :: Symbol) (edge :: Edge) v (subTree :: Tree) (tree :: Tree) proxy union. (KnownSymbol name, edge ~ 'Edge name 'Nullable v subTree, tree ~ 'Node 'Sum '[edge]) => proxy name -> (v -> union) -> ObjectEncoder subTree v -> Tag ObjectEncoder union tree (v -> Result ObjectEncoder union) Source # | |
FieldSYM ObjectEncoder Source # | |
Defined in Typson.JsonTree Methods field :: forall (key :: Symbol) (edge :: Edge) field (subTree :: Tree) (tree :: Tree) proxy obj. (KnownSymbol key, edge ~ 'Edge key 'Singleton field subTree, tree ~ 'Node 'Product '[edge]) => proxy key -> (obj -> field) -> ObjectEncoder subTree field -> Field ObjectEncoder obj tree field Source # optField :: forall (key :: Symbol) (edge :: Edge) field (subTree :: Tree) (tree :: Tree) proxy obj. (KnownSymbol key, edge ~ 'Edge key 'Nullable field subTree, tree ~ 'Node 'Product '[edge]) => proxy key -> (obj -> Maybe field) -> ObjectEncoder subTree field -> Field ObjectEncoder obj tree (Maybe field) Source # optFieldDef :: forall (key :: Symbol) (edge :: Edge) field (subTree :: Tree) (tree :: Tree) proxy obj. (KnownSymbol key, edge ~ 'Edge key 'Singleton field subTree, tree ~ 'Node 'Product '[edge]) => proxy key -> (obj -> field) -> field -> ObjectEncoder subTree field -> Field ObjectEncoder obj tree field Source # | |
ObjectSYM ObjectEncoder Source # | |
Defined in Typson.JsonTree Methods object :: forall (tree :: Tree) (edges :: [Edge]) o. (tree ~ 'Node 'Product edges, NoDuplicateKeys o edges) => String -> TreeBuilder (Field ObjectEncoder o) tree o -> ObjectEncoder tree o Source # prim :: (FromJSON v, ToJSON v) => ObjectEncoder 'Leaf v Source # list :: forall (tree :: Tree) o. ObjectEncoder tree o -> ObjectEncoder ('IndexedNode Nat tree) [o] Source # textMap :: forall k (tree :: Tree) o. (FromJSONKey k, ToJSONKey k, IsString k, Ord k) => ObjectEncoder tree o -> ObjectEncoder ('IndexedNode Symbol tree) (Map k o) Source # set :: forall o (tree :: Tree). Ord o => ObjectEncoder tree o -> ObjectEncoder ('IndexedNode Nat tree) (Set o) Source # vector :: forall (tree :: Tree) o. ObjectEncoder tree o -> ObjectEncoder ('IndexedNode Nat tree) (Vector o) Source # | |
newtype Tag ObjectEncoder u t a Source # | |
Defined in Typson.JsonTree | |
newtype Field ObjectEncoder o t a Source # | |
Defined in Typson.JsonTree | |
type Result ObjectEncoder u Source # | |
Defined in Typson.JsonTree |
newtype ObjectDecoder (t :: Tree) o Source #
Use a Tree
to decode a type from an Aeson Value
Constructors
ObjectDecoder | |
Fields
|
Instances
UnionSYM ObjectDecoder Source # | |
Defined in Typson.JsonTree Associated Types type Result ObjectDecoder union Source # data Tag ObjectDecoder :: Type -> Tree -> Type -> Type Source # Methods union :: forall (tree :: Tree) (edges :: [Edge]) union. (tree ~ 'Node 'Sum edges, NoDuplicateKeys union edges) => String -> TreeBuilder (Tag ObjectDecoder union) tree (union -> Result ObjectDecoder union) -> ObjectDecoder tree union Source # tag :: forall (name :: Symbol) (edge :: Edge) v (subTree :: Tree) (tree :: Tree) proxy union. (KnownSymbol name, edge ~ 'Edge name 'Nullable v subTree, tree ~ 'Node 'Sum '[edge]) => proxy name -> (v -> union) -> ObjectDecoder subTree v -> Tag ObjectDecoder union tree (v -> Result ObjectDecoder union) Source # | |
FieldSYM ObjectDecoder Source # | |
Defined in Typson.JsonTree Methods field :: forall (key :: Symbol) (edge :: Edge) field (subTree :: Tree) (tree :: Tree) proxy obj. (KnownSymbol key, edge ~ 'Edge key 'Singleton field subTree, tree ~ 'Node 'Product '[edge]) => proxy key -> (obj -> field) -> ObjectDecoder subTree field -> Field ObjectDecoder obj tree field Source # optField :: forall (key :: Symbol) (edge :: Edge) field (subTree :: Tree) (tree :: Tree) proxy obj. (KnownSymbol key, edge ~ 'Edge key 'Nullable field subTree, tree ~ 'Node 'Product '[edge]) => proxy key -> (obj -> Maybe field) -> ObjectDecoder subTree field -> Field ObjectDecoder obj tree (Maybe field) Source # optFieldDef :: forall (key :: Symbol) (edge :: Edge) field (subTree :: Tree) (tree :: Tree) proxy obj. (KnownSymbol key, edge ~ 'Edge key 'Singleton field subTree, tree ~ 'Node 'Product '[edge]) => proxy key -> (obj -> field) -> field -> ObjectDecoder subTree field -> Field ObjectDecoder obj tree field Source # | |
ObjectSYM ObjectDecoder Source # | |
Defined in Typson.JsonTree Methods object :: forall (tree :: Tree) (edges :: [Edge]) o. (tree ~ 'Node 'Product edges, NoDuplicateKeys o edges) => String -> TreeBuilder (Field ObjectDecoder o) tree o -> ObjectDecoder tree o Source # prim :: (FromJSON v, ToJSON v) => ObjectDecoder 'Leaf v Source # list :: forall (tree :: Tree) o. ObjectDecoder tree o -> ObjectDecoder ('IndexedNode Nat tree) [o] Source # textMap :: forall k (tree :: Tree) o. (FromJSONKey k, ToJSONKey k, IsString k, Ord k) => ObjectDecoder tree o -> ObjectDecoder ('IndexedNode Symbol tree) (Map k o) Source # set :: forall o (tree :: Tree). Ord o => ObjectDecoder tree o -> ObjectDecoder ('IndexedNode Nat tree) (Set o) Source # vector :: forall (tree :: Tree) o. ObjectDecoder tree o -> ObjectDecoder ('IndexedNode Nat tree) (Vector o) Source # | |
newtype Tag ObjectDecoder u t a Source # | |
Defined in Typson.JsonTree | |
newtype Field ObjectDecoder o t a Source # | |
Defined in Typson.JsonTree | |
type Result ObjectDecoder u Source # | |
Defined in Typson.JsonTree |
newtype ObjectTree (t :: Tree) o Source #
Used to pass a Tree
around at the value level.
Constructors
ObjectTree | |
Fields
|
Instances
UnionSYM ObjectTree Source # | |
Defined in Typson.JsonTree Associated Types type Result ObjectTree union Source # data Tag ObjectTree :: Type -> Tree -> Type -> Type Source # Methods union :: forall (tree :: Tree) (edges :: [Edge]) union. (tree ~ 'Node 'Sum edges, NoDuplicateKeys union edges) => String -> TreeBuilder (Tag ObjectTree union) tree (union -> Result ObjectTree union) -> ObjectTree tree union Source # tag :: forall (name :: Symbol) (edge :: Edge) v (subTree :: Tree) (tree :: Tree) proxy union. (KnownSymbol name, edge ~ 'Edge name 'Nullable v subTree, tree ~ 'Node 'Sum '[edge]) => proxy name -> (v -> union) -> ObjectTree subTree v -> Tag ObjectTree union tree (v -> Result ObjectTree union) Source # | |
FieldSYM ObjectTree Source # | |
Defined in Typson.JsonTree Methods field :: forall (key :: Symbol) (edge :: Edge) field (subTree :: Tree) (tree :: Tree) proxy obj. (KnownSymbol key, edge ~ 'Edge key 'Singleton field subTree, tree ~ 'Node 'Product '[edge]) => proxy key -> (obj -> field) -> ObjectTree subTree field -> Field ObjectTree obj tree field Source # optField :: forall (key :: Symbol) (edge :: Edge) field (subTree :: Tree) (tree :: Tree) proxy obj. (KnownSymbol key, edge ~ 'Edge key 'Nullable field subTree, tree ~ 'Node 'Product '[edge]) => proxy key -> (obj -> Maybe field) -> ObjectTree subTree field -> Field ObjectTree obj tree (Maybe field) Source # optFieldDef :: forall (key :: Symbol) (edge :: Edge) field (subTree :: Tree) (tree :: Tree) proxy obj. (KnownSymbol key, edge ~ 'Edge key 'Singleton field subTree, tree ~ 'Node 'Product '[edge]) => proxy key -> (obj -> field) -> field -> ObjectTree subTree field -> Field ObjectTree obj tree field Source # | |
ObjectSYM ObjectTree Source # | |
Defined in Typson.JsonTree Methods object :: forall (tree :: Tree) (edges :: [Edge]) o. (tree ~ 'Node 'Product edges, NoDuplicateKeys o edges) => String -> TreeBuilder (Field ObjectTree o) tree o -> ObjectTree tree o Source # prim :: (FromJSON v, ToJSON v) => ObjectTree 'Leaf v Source # list :: forall (tree :: Tree) o. ObjectTree tree o -> ObjectTree ('IndexedNode Nat tree) [o] Source # textMap :: forall k (tree :: Tree) o. (FromJSONKey k, ToJSONKey k, IsString k, Ord k) => ObjectTree tree o -> ObjectTree ('IndexedNode Symbol tree) (Map k o) Source # set :: forall o (tree :: Tree). Ord o => ObjectTree tree o -> ObjectTree ('IndexedNode Nat tree) (Set o) Source # vector :: forall (tree :: Tree) o. ObjectTree tree o -> ObjectTree ('IndexedNode Nat tree) (Vector o) Source # | |
data Tag ObjectTree u t a Source # | |
Defined in Typson.JsonTree | |
data Field ObjectTree o t a Source # | |
Defined in Typson.JsonTree | |
type Result ObjectTree u Source # | |
Defined in Typson.JsonTree |
Specialized Indexed Free Applicative
data TreeBuilder (f :: Tree -> Type -> Type) (t :: Tree) (a :: Type) Source #
An indexed free applicative variant that is used to build Tree
s by
gathering up all the edges.
(<<$>) :: (a -> b) -> f ('Node aggr '[edge]) a -> TreeBuilder f ('Node aggr '[edge]) b infixl 4 Source #
Used like <$>
in schema definitions
(<<*>) :: TreeBuilder f ('Node aggr edges) (a -> b) -> f ('Node aggr '[edge]) a -> TreeBuilder f ('Node aggr (edge ': edges)) b infixl 4 Source #
Used like <*>
in schema definitions
runAp :: Applicative g => (forall a' t'. f t' a' -> g a') -> TreeBuilder f t a -> g a Source #
runAp_ :: Monoid m => (forall a' t'. f t' a' -> m) -> TreeBuilder f t a -> m Source #
Core Data Structure
This is the data structure used to represent the JSON form of a haskell type. It is
only used at the type level via the DataKinds
extension. You shouldn't write
this type yourself, instead it's recommended that you let the compiler infer
it using the PartialTypeSignatures
extension and turning off warnings for
partial signatures using -fno-warn-partial-type-signatures
. The Tree
argument in the type signatures of your schemas can then be filled with _
.
personJ :: JsonSchema _ Person
Constructors
Node Aggregator [Edge] | |
IndexedNode Type Tree | A node representing a container indexed by some kind |
Leaf |
data Aggregator Source #
data Multiplicity Source #
type family NoDuplicateKeys (obj :: Type) (edges :: [Edge]) :: Constraint where ... Source #
A constraint that raises a type error if an object has more than one field with the same key.
Equations
NoDuplicateKeys obj ('Edge key q ty subTree ': rest) = (KeyNotPresent key obj rest, NoDuplicateKeys obj rest) | |
NoDuplicateKeys obj '[] = () |