| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Schemas.Untyped
Synopsis
- data Schema
- data Field = Field {- fieldSchema :: Schema
- isRequired :: Bool
 
- pattern Empty :: Schema
- pattern Union :: NonEmpty (Text, Schema) -> Schema
- _Empty :: Prism' Schema ()
- _Union :: Prism' Schema (NonEmpty (Text, Schema))
- finite :: Natural -> Schema -> Schema
- finiteValue :: Validators -> Natural -> Schema -> Value -> Value
- versions :: Schema -> NonEmpty Schema
- type Trace = [Text]
- data Mismatch- = MissingRecordField { }
- | MissingEnumChoices { }
- | OptionalRecordField { }
- | InvalidRecordField { - name :: Text
- mismatches :: [Mismatch]
 
- | InvalidEnumValue { }
- | InvalidConstructor { }
- | InvalidUnionValue { }
- | SchemaMismatch { }
- | ValueMismatch { }
- | EmptyAllOf
- | PrimValidatorMissing { }
- | PrimError { }
- | InvalidChoice { - choiceNumber :: Int
 
- | TryFailed { }
- | AllAlternativesFailed { - mismatches :: [Mismatch]
 
 
- type Validators = HashMap Text ValidatePrim
- type ValidatePrim = Value -> Maybe Text
- validate :: Validators -> Schema -> Value -> [(Trace, Mismatch)]
- isSubtypeOf :: Validators -> Schema -> Schema -> Either [(Trace, Mismatch)] (Value -> Value)
- type Path = Int
- selectPath :: Path -> [a] -> Maybe a
- tag :: Int -> Text
- decodeAlternatives :: Value -> [(Value, Path)]
- encodeAlternatives :: NonEmpty Value -> Value
- lookup :: (Eq a, Foldable f) => a -> f (a, b) -> Maybe b
- emptyValue :: Value
Documentation
A schema for untyped data, such as JSON or XML.
- introduction forms: extractSchema,theSchema,mempty
- operations: isSubtypeOf,versions,coerce,validate
- composition: '(<>)'
Constructors
| Array Schema | |
| StringMap Schema | |
| Enum (NonEmpty Text) | |
| Record (HashMap Text Field) | |
| AllOf (NonEmpty Schema) | Encoding and decoding work for all alternatives | 
| OneOf (NonEmpty Schema) | Decoding works for all alternatives, encoding only for one | 
| Prim Text | Carries the name of primitive type | 
Instances
Constructors
| Field | |
| Fields 
 | |
Instances
| Eq Field Source # | |
| Show Field Source # | |
| Generic Field Source # | |
| HasSchema Field Source # | |
| Defined in Schemas.Class Methods | |
| type Rep Field Source # | |
| Defined in Schemas.Untyped type Rep Field = D1 (MetaData "Field" "Schemas.Untyped" "schemas-0.1.1.0-9zDZuHVzzF7Fl693Gilt6H" False) (C1 (MetaCons "Field" PrefixI True) (S1 (MetaSel (Just "fieldSchema") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Schema) :*: S1 (MetaSel (Just "isRequired") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))) | |
finite :: Natural -> Schema -> Schema Source #
Ensure that a Schema is finite by enforcing a max depth.
   The result is guaranteed to be a supertype of the input.
finiteValue :: Validators -> Natural -> Schema -> Value -> Value Source #
Ensure that a Value is finite by enforcing a max depth in a schema preserving way
versions :: Schema -> NonEmpty Schema Source #
Flattens alternatives. Returns a schema without AllOf constructors
Constructors
Instances
| Eq Mismatch Source # | |
| Show Mismatch Source # | |
| Exception Mismatch Source # | |
| Defined in Schemas.Untyped Methods toException :: Mismatch -> SomeException # fromException :: SomeException -> Maybe Mismatch # displayException :: Mismatch -> String # | |
type Validators = HashMap Text ValidatePrim Source #
validate :: Validators -> Schema -> Value -> [(Trace, Mismatch)] Source #
Structural validation of a JSON value against a schema Ignores extraneous fields in records
isSubtypeOf :: Validators -> Schema -> Schema -> Either [(Trace, Mismatch)] (Value -> Value) Source #
sub  returns a witness that isSubtypeOf supsub is a subtype of sup, i.e. a cast function sub -> sup
Array Bool `isSubtypeOf` Bool
Just function
 > Record [("a", Bool)] isSubtypeOf Record [("a", Number)]
   Nothing
selectPath :: Path -> [a] -> Maybe a Source #
emptyValue :: Value Source #