| Maintainer | Brandon Chinn <brandon@leapyear.io> |
|---|---|
| Stability | experimental |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Aeson.Schema.Internal
Description
Internal definitions for declaring JSON schemas.
Synopsis
- newtype Object (schema :: SchemaType) = UnsafeObject (HashMap Text Dynamic)
- type IsSchemaObject schema = (IsSchemaType schema, SchemaResult schema ~ Object schema)
- data SchemaType
- toSchemaTypeShow :: forall (a :: SchemaType). Typeable a => SchemaType
- showSchema :: forall (a :: SchemaType). Typeable a => String
- data SchemaKey
- type family FromSchemaKey (schemaKey :: SchemaKey) where ...
- fromSchemaKey :: forall schemaKey. KnownSymbol (FromSchemaKey schemaKey) => Text
- class (Typeable schemaKey, KnownSymbol (FromSchemaKey schemaKey)) => KnownSchemaKey (schemaKey :: SchemaKey) where
- getContext :: HashMap Text Value -> Value
- type family SchemaResult (schema :: SchemaType) where ...
- type family SchemaResultList (xs :: [SchemaType]) where ...
- class Typeable schema => IsSchemaType (schema :: SchemaType) where
- parseValue :: [Text] -> Value -> Parser (SchemaResult schema)
- showValue :: SchemaResult schema -> String
- parseFail :: forall (schema :: SchemaType) m a. (MonadFail m, Typeable schema) => [Text] -> Value -> m a
- data UnSchemaKey :: SchemaKey -> Exp Symbol
- type Lookup a = Map Snd <=< Find (TyEq a <=< Fst)
- type family LookupSchema (key :: Symbol) (schema :: SchemaType) :: SchemaType where ...
- getKey :: forall key schema endSchema result. (endSchema ~ LookupSchema key schema, result ~ SchemaResult endSchema, KnownSymbol key, Typeable result, Typeable endSchema) => Object schema -> result
Documentation
newtype Object (schema :: SchemaType) Source #
The object containing JSON data and its schema.
Has a FromJSON instance, so you can use the usual Aeson decoding functions.
obj = decode "{\"a\": 1}" :: Maybe (Object [schema| { a: Int } |])Constructors
| UnsafeObject (HashMap Text Dynamic) |
Instances
| IsSchemaObject schema => Show (Object schema) Source # | |
| IsSchemaObject schema => FromJSON (Object schema) Source # | |
type IsSchemaObject schema = (IsSchemaType schema, SchemaResult schema ~ Object schema) Source #
A constraint that checks if the given schema is a 'SchemaObject.
data SchemaType Source #
The type-level schema definition for JSON data.
To view a schema for debugging, use showSchema.
Constructors
Instances
| (KnownSchemaKey schemaKey, IsSchemaType inner, Show (SchemaResult inner), Typeable (SchemaResult inner), IsSchemaObject (SchemaObject rest), Typeable rest) => IsSchemaType (SchemaObject ((,) schemaKey inner ': rest)) Source # | |
Defined in Data.Aeson.Schema.Internal Methods parseValue :: [Text] -> Value -> Parser (SchemaResult (SchemaObject ((schemaKey, inner) ': rest))) Source # showValue :: SchemaResult (SchemaObject ((schemaKey, inner) ': rest)) -> String Source # | |
| IsSchemaType (SchemaObject ([] :: [(SchemaKey, SchemaType)])) Source # | |
Defined in Data.Aeson.Schema.Internal Methods parseValue :: [Text] -> Value -> Parser (SchemaResult (SchemaObject [])) Source # showValue :: SchemaResult (SchemaObject []) -> String Source # | |
toSchemaTypeShow :: forall (a :: SchemaType). Typeable a => SchemaType Source #
Convert SchemaType into SchemaType.
showSchema :: forall (a :: SchemaType). Typeable a => String Source #
Pretty show the given SchemaType.
The type-level analogue of SchemaKey.
Constructors
| NormalKey Symbol | |
| PhantomKey Symbol |
Instances
| (KnownSchemaKey schemaKey, IsSchemaType inner, Show (SchemaResult inner), Typeable (SchemaResult inner), IsSchemaObject (SchemaObject rest), Typeable rest) => IsSchemaType (SchemaObject ((,) schemaKey inner ': rest)) Source # | |
Defined in Data.Aeson.Schema.Internal Methods parseValue :: [Text] -> Value -> Parser (SchemaResult (SchemaObject ((schemaKey, inner) ': rest))) Source # showValue :: SchemaResult (SchemaObject ((schemaKey, inner) ': rest)) -> String Source # | |
| IsSchemaType (SchemaObject ([] :: [(SchemaKey, SchemaType)])) Source # | |
Defined in Data.Aeson.Schema.Internal Methods parseValue :: [Text] -> Value -> Parser (SchemaResult (SchemaObject [])) Source # showValue :: SchemaResult (SchemaObject []) -> String Source # | |
type family FromSchemaKey (schemaKey :: SchemaKey) where ... Source #
Equations
| FromSchemaKey (NormalKey key) = key | |
| FromSchemaKey (PhantomKey key) = key |
fromSchemaKey :: forall schemaKey. KnownSymbol (FromSchemaKey schemaKey) => Text Source #
class (Typeable schemaKey, KnownSymbol (FromSchemaKey schemaKey)) => KnownSchemaKey (schemaKey :: SchemaKey) where Source #
Instances
| KnownSymbol key => KnownSchemaKey (NormalKey key) Source # | |
Defined in Data.Aeson.Schema.Internal | |
| KnownSymbol key => KnownSchemaKey (PhantomKey key) Source # | |
Defined in Data.Aeson.Schema.Internal | |
type family SchemaResult (schema :: SchemaType) where ... Source #
A type family mapping SchemaType to the corresponding Haskell type.
Equations
| SchemaResult SchemaBool = Bool | |
| SchemaResult SchemaInt = Int | |
| SchemaResult SchemaDouble = Double | |
| SchemaResult SchemaText = Text | |
| SchemaResult (SchemaCustom inner) = inner | |
| SchemaResult (SchemaMaybe inner) = Maybe (SchemaResult inner) | |
| SchemaResult (SchemaTry inner) = Maybe (SchemaResult inner) | |
| SchemaResult (SchemaList inner) = [SchemaResult inner] | |
| SchemaResult (SchemaObject inner) = Object (SchemaObject inner) | |
| SchemaResult (SchemaUnion schemas) = SumType (SchemaResultList schemas) |
type family SchemaResultList (xs :: [SchemaType]) where ... Source #
Equations
| SchemaResultList '[] = '[] | |
| SchemaResultList (x ': xs) = SchemaResult x ': SchemaResultList xs |
class Typeable schema => IsSchemaType (schema :: SchemaType) where Source #
A type-class for types that can be parsed from JSON for an associated schema type.
Minimal complete definition
Nothing
Methods
parseValue :: [Text] -> Value -> Parser (SchemaResult schema) Source #
parseValue :: FromJSON (SchemaResult schema) => [Text] -> Value -> Parser (SchemaResult schema) Source #
showValue :: SchemaResult schema -> String Source #
showValue :: Show (SchemaResult schema) => SchemaResult schema -> String Source #
Instances
parseFail :: forall (schema :: SchemaType) m a. (MonadFail m, Typeable 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 # | |
Defined in Data.Aeson.Schema.Internal | |
| type Eval (UnSchemaKey (PhantomKey key) :: Symbol -> Type) Source # | |
Defined in Data.Aeson.Schema.Internal | |
type family LookupSchema (key :: Symbol) (schema :: SchemaType) :: SchemaType where ... Source #
The type-level function that return the schema of the given key in a SchemaObject.
Equations
| LookupSchema key (SchemaObject 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)) | |
| LookupSchema key schema = TypeError (((Text "Attempted to lookup key '" :<>: Text key) :<>: Text "' in the following schema:") :$$: ShowType schema) |
getKey :: forall key schema endSchema result. (endSchema ~ LookupSchema key schema, result ~ SchemaResult endSchema, KnownSymbol key, Typeable result, Typeable endSchema) => 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 @"foo" o :: Bool
getKey @"bar" o :: Object ('SchemaObject '[ '("name", 'SchemaText) ])
getKey @"name" $ getKey @"bar" o :: Text
getKey @"baz" o :: Maybe Bool