Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module defines a generic representation of values belonging to a schema, for use during data migration.
Synopsis
- data Value
- type Record = [Field]
- data Field = Field {}
- fromDefaultValue :: NormAPI -> APIType -> DefaultValue -> Maybe Value
- fromJSON :: NormAPI -> APIType -> Value -> Either [(JSONError, Position)] (Value, [(JSONWarning, Position)])
- parseJSON :: NormAPI -> APIType -> Value -> ParserWithErrs Value
- encode :: Value -> Encoding
- decode :: NormAPI -> APIType -> Decoder s Value
- matchesNormAPI :: NormAPI -> APIType -> Value -> Position -> Either (ValueError, Position) ()
- expectRecord :: Value -> Position -> Either (ValueError, Position) Record
- expectEnum :: Value -> Position -> Either (ValueError, Position) FieldName
- expectUnion :: Value -> Position -> Either (ValueError, Position) (FieldName, Value)
- expectList :: Value -> Position -> Either (ValueError, Position) [Value]
- expectMaybe :: Value -> Position -> Either (ValueError, Position) (Maybe Value)
- lookupType :: TypeName -> NormAPI -> Either ApplyFailure NormTypeDecl
- recordToMap :: Record -> Map FieldName Value
- mapToRecord :: Map FieldName Value -> Record
- insertField :: FieldName -> Value -> Record -> Record
- renameField :: FieldName -> FieldName -> Record -> Record
- deleteField :: FieldName -> Record -> Record
- findField :: FieldName -> Record -> Maybe (Record, Value, Record)
- joinRecords :: Record -> FieldName -> Value -> Record -> Record
- arbitrary :: NormAPI -> Gen (APIType, Value)
- arbitraryOfType :: NormAPI -> APIType -> Gen Value
- arbitraryJSONValue :: Gen Value
- prop_jsonRoundTrip :: NormAPI -> Property
- prop_jsonGeneric :: ToJSON a => API -> TypeName -> a -> Result
- prop_cborRoundTrip :: NormAPI -> Property
- prop_cborGeneric :: Serialise a => API -> TypeName -> a -> Result
Types
Generic representation of a data value belonging to a schema type. This representation has the following properties:
- it is straightforward to convert into either CBOR or JSON;
- decoding CBOR or parsing JSON requires the schema, and takes advantage of it by introducing type distinctions and interning field names;
- decoding CBOR is relatively efficient.
String !Text | |
UTCTime !UTCTime | |
Bytes !Binary | |
Bool !Bool | |
Int !Int | |
List ![Value] | |
Maybe !(Maybe Value) | |
Union !FieldName !Value | |
Enum !FieldName | |
Record !Record | |
JSON !Value |
type Record = [Field] Source #
A record is represented as a list of (field name, value) pairs.
Invariant: these are in ascending order by field name, and there are no duplicates.
TODO: consider if it would be worth using Map
instead.
Field | |
|
Converting to and from generic values
fromDefaultValue :: NormAPI -> APIType -> DefaultValue -> Maybe Value Source #
Convert a DefaultValue
into a generic Value
, failing if the
type is not compatible. This requires type information so that it
can introduce type distinctions absent in DefaultValue
, e.g. when
DefValList
is used at type
.TyMaybe
(TyList
t)
fromJSON :: NormAPI -> APIType -> Value -> Either [(JSONError, Position)] (Value, [(JSONWarning, Position)]) Source #
decode :: NormAPI -> APIType -> Decoder s Value Source #
Efficiently decode CBOR as a generic Value
, given the schema
and expected type.
Data validation
matchesNormAPI :: NormAPI -> APIType -> Value -> Position -> Either (ValueError, Position) () Source #
Check that the value is of the given type in the schema, reporting the first error encountered if it does not conform.
expectRecord :: Value -> Position -> Either (ValueError, Position) Record Source #
expectEnum :: Value -> Position -> Either (ValueError, Position) FieldName Source #
expectUnion :: Value -> Position -> Either (ValueError, Position) (FieldName, Value) Source #
expectList :: Value -> Position -> Either (ValueError, Position) [Value] Source #
expectMaybe :: Value -> Position -> Either (ValueError, Position) (Maybe Value) Source #
lookupType :: TypeName -> NormAPI -> Either ApplyFailure NormTypeDecl Source #
Manipulating records
insertField :: FieldName -> Value -> Record -> Record Source #
Insert a (field, value) pair into a record, replacing the existing field if it is present and preserving the ordering invariant.
renameField :: FieldName -> FieldName -> Record -> Record Source #
Rename a field in a record, preserving the ordering invariant.
deleteField :: FieldName -> Record -> Record Source #
Delete a field from a record, trivially preserving the ordering invariant.
findField :: FieldName -> Record -> Maybe (Record, Value, Record) Source #
Split a record at a given field, returning the preceding fields, value and succeeding fields. Fails if the field is absent.
joinRecords :: Record -> FieldName -> Value -> Record -> Record Source #
Join together two records with a (field, value) pair in between. The ordering invariant is not checked!
QuickCheck test infrastructure
arbitrary :: NormAPI -> Gen (APIType, Value) Source #
Given a schema, generate an arbitrary type corresponding to the schema and an arbitrary value of that type.
arbitraryOfType :: NormAPI -> APIType -> Gen Value Source #
Given a schema and a type, generate an arbitrary value of that type.
prop_jsonRoundTrip :: NormAPI -> Property Source #
QuickCheck property that converting a Value
to and from JSON
gives back the original value.
prop_jsonGeneric :: ToJSON a => API -> TypeName -> a -> Result Source #
QuickCheck property that the type-specific JSON serialisation agrees with deserialising as generic JSON and then serialising again.