typson-core-0.1.0.1: Type-safe PostgreSQL JSON Querying
Copyright(c) Aaron Allen 2020
LicenseBSD-style (see the file LICENSE)
MaintainerAaron Allen <aaronallen8455@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Typson.JsonTree

Description

 
Synopsis

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

object Source #

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.

list Source #

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"

textMap Source #

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.

set Source #

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.

vector Source #

Arguments

:: repr tree o

Element schema

-> repr ('IndexedNode Nat tree) (Vector o) 

Construct a Vector schema given a schema for it's elements.

Instances

Instances details
ObjectSYM ObjectDecoder Source # 
Instance details

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 #

ObjectSYM ObjectEncoder Source # 
Instance details

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 #

ObjectSYM ObjectTree Source # 
Instance details

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 #

class FieldSYM repr where Source #

Minimal complete definition

field, optField

Associated Types

data Field repr :: Type -> Tree -> Type -> Type Source #

Methods

field Source #

Arguments

:: (KnownSymbol key, edge ~ 'Edge key 'Singleton field subTree, tree ~ 'Node 'Product '[edge]) 
=> proxy key

The Symbol to use as the key in the JSON object

-> (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

optField Source #

Arguments

:: (KnownSymbol key, edge ~ 'Edge key 'Nullable field subTree, tree ~ 'Node 'Product '[edge]) 
=> proxy key

The Symbol to use as the key in the JSON object

-> (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.

optFieldDef Source #

Arguments

:: (KnownSymbol key, edge ~ 'Edge key 'Singleton field subTree, tree ~ 'Node 'Product '[edge]) 
=> proxy key

The Symbol to use as the key in the JSON object

-> (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

Instances details
FieldSYM ObjectDecoder Source # 
Instance details

Defined in Typson.JsonTree

Associated Types

data Field ObjectDecoder :: Type -> Tree -> Type -> Type Source #

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 # 
Instance details

Defined in Typson.JsonTree

Associated Types

data Field ObjectEncoder :: Type -> Tree -> Type -> Type Source #

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 # 
Instance details

Defined in Typson.JsonTree

Associated Types

data Field ObjectTree :: Type -> Tree -> Type -> Type Source #

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.

Associated Types

type Result repr union :: Type Source #

The result produced from each tag

data Tag repr :: Type -> Tree -> Type -> Type Source #

Methods

union Source #

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.

tag Source #

Arguments

:: (KnownSymbol name, edge ~ 'Edge name 'Nullable v subTree, tree ~ 'Node 'Sum '[edge]) 
=> proxy name

Symbol used as the JSON key for the field

-> (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

Instances details
UnionSYM ObjectDecoder Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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

key :: Proxy (key :: Symbol) Source #

A synonym for Proxy that takes a Symbol. Intended to be used in field and tag definitions.

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

  • encodeObject :: o -> Value

    Uses a schema as a JSON encoder

       instance ToJSON Person where
         toJSON = encodeObject personJ
    

Instances

Instances details
UnionSYM ObjectEncoder Source # 
Instance details

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 # 
Instance details

Defined in Typson.JsonTree

Associated Types

data Field ObjectEncoder :: Type -> Tree -> Type -> Type Source #

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 # 
Instance details

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 # 
Instance details

Defined in Typson.JsonTree

newtype Tag ObjectEncoder u t a = TagEncoder {}
newtype Field ObjectEncoder o t a Source # 
Instance details

Defined in Typson.JsonTree

type Result ObjectEncoder u Source # 
Instance details

Defined in Typson.JsonTree

newtype ObjectDecoder (t :: Tree) o Source #

Use a Tree to decode a type from an Aeson Value

Constructors

ObjectDecoder 

Fields

  • decodeObject :: Value -> Parser o

    Uses a schema as a JSON parser

       instance FromJSON Person where
         parseJSON = decodeObject personJ
    

Instances

Instances details
UnionSYM ObjectDecoder Source # 
Instance details

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 # 
Instance details

Defined in Typson.JsonTree

Associated Types

data Field ObjectDecoder :: Type -> Tree -> Type -> Type Source #

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 # 
Instance details

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 # 
Instance details

Defined in Typson.JsonTree

newtype Field ObjectDecoder o t a Source # 
Instance details

Defined in Typson.JsonTree

type Result ObjectDecoder u Source # 
Instance details

Defined in Typson.JsonTree

type Result ObjectDecoder u = ()

newtype ObjectTree (t :: Tree) o Source #

Used to pass a Tree around at the value level.

Constructors

ObjectTree 

Fields

Instances

Instances details
UnionSYM ObjectTree Source # 
Instance details

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 # 
Instance details

Defined in Typson.JsonTree

Associated Types

data Field ObjectTree :: Type -> Tree -> Type -> Type Source #

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 # 
Instance details

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 # 
Instance details

Defined in Typson.JsonTree

data Tag ObjectTree u t a = TagProxy
data Field ObjectTree o t a Source # 
Instance details

Defined in Typson.JsonTree

type Result ObjectTree u Source # 
Instance details

Defined in Typson.JsonTree

type Result ObjectTree u = ()

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 Trees 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

data Tree Source #

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 Edge Source #

Constructors

Edge 

Fields

data Aggregator Source #

Constructors

Product

Object has all fields from a list

Sum

Object has exactly one field from a list of possible fields

data Multiplicity Source #

Constructors

Singleton

A non-null field

Nullable

A field that can be null

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 '[] = ()