aeson-schemas-1.3.2: Easily consume JSON data on-demand with type-safety

MaintainerBrandon Chinn <brandon@leapyear.io>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Data.Aeson.Schema.Internal

Description

Internal definitions for declaring JSON schemas.

Synopsis

Documentation

newtype 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 } |])
Instances
IsSchema schema => Eq (Object schema) Source # 
Instance details

Defined in Data.Aeson.Schema.Internal

Methods

(==) :: Object schema -> Object schema -> Bool #

(/=) :: Object schema -> Object schema -> Bool #

IsSchema schema => Show (Object schema) Source # 
Instance details

Defined in Data.Aeson.Schema.Internal

Methods

showsPrec :: Int -> Object schema -> ShowS #

show :: Object schema -> String #

showList :: [Object schema] -> ShowS #

IsSchema schema => ToJSON (Object schema) Source # 
Instance details

Defined in Data.Aeson.Schema.Internal

Methods

toJSON :: Object schema -> Value #

toEncoding :: Object schema -> Encoding #

toJSONList :: [Object schema] -> Value #

toEncodingList :: [Object schema] -> Encoding #

IsSchema schema => FromJSON (Object schema) Source # 
Instance details

Defined in Data.Aeson.Schema.Internal

Methods

parseJSON :: Value -> Parser (Object schema) #

parseJSONList :: Value -> Parser [Object schema] #

toMap :: IsSchema (Schema schema) => Object (Schema schema) -> Object Source #

Convert an Object into a HashMap, losing the type information in the schema.

Since: 1.3.0

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 @MySchema

showSchemaType :: forall (schemaType :: SchemaType). HasSchemaResult schemaType => String Source #

type family SchemaResult (schema :: SchemaType) where ... Source #

A type family mapping SchemaType to the corresponding Haskell type.

type family SchemaResultList (xs :: [SchemaType]) where ... Source #

Equations

SchemaResultList '[] = '[] 
SchemaResultList (x ': xs) = SchemaResult x ': SchemaResultList xs 

class IsSchemaType schema => HasSchemaResult (schema :: SchemaType) where Source #

A type-class for types that can be parsed from JSON for an associated schema type.

Minimal complete definition

Nothing

Instances
(Show inner, Typeable inner, FromJSON inner, ToJSON inner) => HasSchemaResult (SchemaScalar inner :: SchemaType' Symbol Type) Source # 
Instance details

Defined in Data.Aeson.Schema.Internal

(HasSchemaResult inner, Show (SchemaResult inner), ToJSON (SchemaResult inner)) => HasSchemaResult (SchemaMaybe inner) Source # 
Instance details

Defined in Data.Aeson.Schema.Internal

(HasSchemaResult inner, Show (SchemaResult inner), ToJSON (SchemaResult inner)) => HasSchemaResult (SchemaTry inner) Source # 
Instance details

Defined in Data.Aeson.Schema.Internal

(HasSchemaResult inner, Show (SchemaResult inner), ToJSON (SchemaResult inner)) => HasSchemaResult (SchemaList inner) Source # 
Instance details

Defined in Data.Aeson.Schema.Internal

(All HasSchemaResult schemas, All IsSchemaType schemas, Show (SchemaResult (SchemaUnion schemas)), FromJSON (SchemaResult (SchemaUnion schemas)), ToJSON (SchemaResult (SchemaUnion schemas)), ParseSumType schemas) => HasSchemaResult (SchemaUnion schemas) Source # 
Instance details

Defined in Data.Aeson.Schema.Internal

(All HasSchemaResultPair pairs, IsSchemaObjectMap pairs) => HasSchemaResult (SchemaObject pairs) Source # 
Instance details

Defined in Data.Aeson.Schema.Internal

IsSchema schema => HasSchemaResult (SchemaInclude (Right schema :: Either Type Schema)) Source # 
Instance details

Defined in Data.Aeson.Schema.Internal

class ParseSumType xs where Source #

Instances
ParseSumType ([] :: [SchemaType]) Source # 
Instance details

Defined in Data.Aeson.Schema.Internal

(HasSchemaResult schema, ParseSumType schemas) => ParseSumType (schema ': schemas) Source # 
Instance details

Defined in Data.Aeson.Schema.Internal

Methods

parseSumType :: [Text] -> Value -> Parser (SumType (SchemaResultList (schema ': schemas))) Source #

toValueMap :: forall pairs. All HasSchemaResultPair pairs => Object (Schema pairs) -> Object Source #

class HasSchemaResultPair (a :: (SchemaKey, SchemaType)) where Source #

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

Defined in Data.Aeson.Schema.Internal

Methods

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

toValuePair :: Proxy (key, inner) -> Object schema -> Object Source #

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

parseFail :: forall (schema :: SchemaType) m a. (MonadFail m, HasSchemaResult schema) => [Text] -> Value -> m a Source #

A helper for creating fail messages when parsing a schema.

data UnSchemaKey :: SchemaKey -> Exp Symbol Source #

Instances
type Eval (UnSchemaKey (NormalKey key) :: Symbol -> Type) Source # 
Instance details

Defined in Data.Aeson.Schema.Internal

type Eval (UnSchemaKey (NormalKey key) :: Symbol -> Type) = Eval (Pure key)
type Eval (UnSchemaKey (PhantomKey key) :: Symbol -> Type) Source # 
Instance details

Defined in Data.Aeson.Schema.Internal

type Eval (UnSchemaKey (PhantomKey key) :: Symbol -> Type) = Eval (Pure key)

type family LookupSchema (key :: Symbol) (schema :: Schema) :: SchemaType where ... Source #

The type-level function that return the schema of the given key in a SchemaObject.

Equations

LookupSchema key (Schema schema) = Eval (FromMaybe (TypeError (((Text "Key '" :<>: Text key) :<>: Text "' does not exist in the following schema:") :$$: ShowType schema)) =<< (Lookup key =<< Map (Bimap UnSchemaKey Pure) schema)) 

getKey :: forall (key :: Symbol) (schema :: Schema) (endSchema :: SchemaType) result. (endSchema ~ LookupSchema key schema, result ~ SchemaResult endSchema, KnownSymbol key, Typeable result, Typeable endSchema) => Proxy key -> Object schema -> result Source #

Get a key from the given Object, returned as the type encoded in its schema.

let o = .. :: Object
            ( 'SchemaObject
               '[ '("foo", 'SchemaInt)
                , '("bar", 'SchemaObject
                     '[ '("name", 'SchemaText)
                      ]
                , '("baz", 'SchemaMaybe 'SchemaBool)
                ]
            )

getKey (Proxy @"foo") o                  :: Bool
getKey (Proxy @"bar") o                  :: Object ('SchemaObject '[ '("name", 'SchemaText) ])
getKey (Proxy @"name") $ getKey @"bar" o :: Text
getKey (Proxy @"baz") o                  :: Maybe Bool

unsafeGetKey :: forall (endSchema :: SchemaType) (key :: Symbol) (schema :: Schema). (KnownSymbol key, Typeable (SchemaResult endSchema)) => Proxy key -> Object schema -> SchemaResult endSchema Source #