aeson-schemas-1.4.0.1: Easily consume JSON data on-demand with type-safety
MaintainerBrandon Chinn <brandon@leapyear.io>
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Aeson.Schema.Key

Description

Defines a SchemaKey.

Synopsis

Documentation

data SchemaKey' s Source #

A key in a JSON object schema.

Constructors

NormalKey s 
PhantomKey s

A key that doesn't actually exist in the object, but whose content should be parsed from the current object.

Instances

Instances details
Generic (SchemaKey' s) Source # 
Instance details

Defined in Data.Aeson.Schema.Key

Associated Types

type Rep (SchemaKey' s) :: Type -> Type #

Methods

from :: SchemaKey' s -> Rep (SchemaKey' s) x #

to :: Rep (SchemaKey' s) x -> SchemaKey' s #

Show s => Show (SchemaKey' s) Source # 
Instance details

Defined in Data.Aeson.Schema.Key

Eq s => Eq (SchemaKey' s) Source # 
Instance details

Defined in Data.Aeson.Schema.Key

Methods

(==) :: SchemaKey' s -> SchemaKey' s -> Bool #

(/=) :: SchemaKey' s -> SchemaKey' s -> Bool #

Hashable s => Hashable (SchemaKey' s) Source # 
Instance details

Defined in Data.Aeson.Schema.Key

Methods

hashWithSalt :: Int -> SchemaKey' s -> Int #

hash :: SchemaKey' s -> Int #

Lift s => Lift (SchemaKey' s :: Type) Source # 
Instance details

Defined in Data.Aeson.Schema.Key

Methods

lift :: Quote m => SchemaKey' s -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => SchemaKey' s -> Code m (SchemaKey' s) #

(IsSchemaKey key, HasSchemaResult inner, Typeable (SchemaResult inner)) => HasSchemaResultPair '(key, inner) Source # 
Instance details

Defined in Data.Aeson.Schema.Internal

Methods

parseValuePair :: Proxy '(key, inner) -> [Key] -> Object -> Parser (Key, Dynamic) Source #

toValuePair :: forall (schema :: Schema). Proxy '(key, inner) -> Object schema -> Object Source #

showValuePair :: forall (schema :: Schema). Proxy '(key, inner) -> Object schema -> (String, ShowS) Source #

type Rep (SchemaKey' s) Source # 
Instance details

Defined in Data.Aeson.Schema.Key

type Rep (SchemaKey' s) = D1 ('MetaData "SchemaKey'" "Data.Aeson.Schema.Key" "aeson-schemas-1.4.0.1-5USnmO4FqKEETeKzu5nMV1" 'False) (C1 ('MetaCons "NormalKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 s)) :+: C1 ('MetaCons "PhantomKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 s)))

type SchemaKeyV = SchemaKey' String Source #

A value-level SchemaKey

getContext :: SchemaKeyV -> Object -> Value Source #

Given schema `{ key: innerSchema }` for JSON data `{ key: val1 }`, get the JSON Value that innerSchema should parse.

toContext :: SchemaKeyV -> Value -> Object Source #

Given JSON data val adhering to innerSchema, get the JSON object that should be merged with the outer JSON object.

type SchemaKey = SchemaKey' Symbol Source #

A type-level SchemaKey

class KnownSymbol (FromSchemaKey key) => IsSchemaKey (key :: SchemaKey) where Source #

Associated Types

type FromSchemaKey key :: Symbol Source #

Instances

Instances details
KnownSymbol key => IsSchemaKey ('NormalKey key) Source # 
Instance details

Defined in Data.Aeson.Schema.Key

Associated Types

type FromSchemaKey ('NormalKey key) :: Symbol Source #

KnownSymbol key => IsSchemaKey ('PhantomKey key) Source # 
Instance details

Defined in Data.Aeson.Schema.Key

Associated Types

type FromSchemaKey ('PhantomKey key) :: Symbol Source #

fromSchemaKey :: forall key. IsSchemaKey key => String Source #

showSchemaKey :: forall key. IsSchemaKey key => String Source #