Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype SchemaName = SchemaName String
- data Schema
- data Field = Field {
- fieldSchema :: Schema
- isRequired :: Bool
- fieldSchemaL :: Applicative f => (Schema -> f Schema) -> Field -> f Field
- pattern Empty :: Schema
- pattern Union :: NonEmpty (Text, Schema) -> Schema
- _Empty :: Prism' Schema ()
- _Union :: Prism' Schema (NonEmpty (Text, Schema))
- type Trace = [Text]
- data Mismatch
- = MissingRecordField { }
- | MissingEnumChoices { }
- | OptionalRecordField { }
- | InvalidRecordField {
- name :: Text
- mismatches :: [(Trace, Mismatch)]
- | InvalidEnumValue { }
- | InvalidConstructor { }
- | InvalidUnionValue { }
- | SchemaMismatch { }
- | ValueMismatch { }
- | EmptyAllOf
- | PrimValidatorMissing { }
- | PrimError { }
- | PrimMismatch { }
- | InvalidChoice {
- choiceNumber :: Int
- | TryFailed { }
- | UnusedFields [[Text]]
- | AllAlternativesFailed {
- mismatches :: [(Trace, Mismatch)]
- | UnexpectedAllOf
- | NoMatches
- 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)]
- lookup :: (Eq a, Foldable f) => a -> f (a, b) -> Maybe b
- emptyValue :: Value
Documentation
newtype SchemaName Source #
Instances
Eq SchemaName Source # | |
Defined in Schemas.Untyped (==) :: SchemaName -> SchemaName -> Bool # (/=) :: SchemaName -> SchemaName -> Bool # | |
Show SchemaName Source # | |
Defined in Schemas.Untyped showsPrec :: Int -> SchemaName -> ShowS # show :: SchemaName -> String # showList :: [SchemaName] -> ShowS # | |
IsString SchemaName Source # | |
Defined in Schemas.Untyped fromString :: String -> SchemaName # | |
HasSchema SchemaName Source # | |
Defined in Schemas.Class |
A schema for untyped data, such as JSON or XML.
- introduction forms:
extractSchema
,theSchema
,mempty
- operations:
isSubtypeOf
,versions
,coerce
,validate
- composition: '(<>)'
Array Schema | |
StringMap Schema | |
Enum (NonEmpty Text) | |
Record (HashMap Text Field) | |
OneOf (NonEmpty Schema) | Decoding works for all alternatives, encoding only for one |
Prim Text | Carries the name of primitive type |
Named SchemaName Schema |
Instances
Field | |
|
Instances
Eq Field Source # | |
Show Field Source # | |
Generic Field Source # | |
HasSchema Field Source # | |
Defined in Schemas.Class | |
type Rep Field Source # | |
Defined in Schemas.Untyped type Rep Field = D1 (MetaData "Field" "Schemas.Untyped" "schemas-0.3.0-JAYuDPycTib4oO1qL86IJR" False) (C1 (MetaCons "Field" PrefixI True) (S1 (MetaSel (Just "fieldSchema") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Schema) :*: S1 (MetaSel (Just "isRequired") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))) |
fieldSchemaL :: Applicative f => (Schema -> f Schema) -> Field -> f Field Source #
Instances
Eq Mismatch Source # | |
Show Mismatch Source # | |
Exception Mismatch Source # | |
Defined in Schemas.Untyped 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 #