| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Schemas.Untyped
Synopsis
- newtype SchemaName = SchemaName String
- data Schema
- data Field = Field {
- fieldSchema :: Schema
- isRequired :: Bool
- fieldSchemaL :: Applicative f => (Schema -> f Schema) -> Field -> f Field
- pattern Unit :: Schema
- pattern Union :: NonEmpty (Text, Schema) -> Schema
- _Unit :: Prism' Schema ()
- _Union :: Prism' Schema (NonEmpty (Text, Schema))
- type Trace = [Text]
- data Mismatch
- = MissingRecordField { }
- | MissingEnumChoices { }
- | OptionalRecordField { }
- | InvalidRecordField { }
- | InvalidEnumValue { }
- | InvalidRecordValue { }
- | InvalidConstructor { }
- | InvalidUnionValue { }
- | SchemaMismatch { }
- | ValueMismatch { }
- | EmptySchema
- | PrimValidatorMissing { }
- | PrimError { }
- | PrimMismatch { }
- | InvalidChoice {
- choiceNumber :: Int
- | UnusedFields (HashSet 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 #
Constructors
| SchemaName String |
Instances
| Eq SchemaName Source # | |
Defined in Schemas.Untyped | |
| Show SchemaName Source # | |
Defined in Schemas.Untyped Methods showsPrec :: Int -> SchemaName -> ShowS # show :: SchemaName -> String # showList :: [SchemaName] -> ShowS # | |
| IsString SchemaName Source # | |
Defined in Schemas.Untyped Methods fromString :: String -> SchemaName # | |
| HasSchema SchemaName Source # | |
Defined in Schemas.Class Methods | |
A schema for untyped data, such as JSON or XML.
- introduction forms:
extractSchema,schemaFor,mempty - operations:
isSubtypeOf,versions,coerce,validate - composition: '(<>)'
Constructors
| 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 | |
| Empty |
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.4.0.0-DT2P1byuCA4Iptxa9MvJ7g" 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 #
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 # | |
| MonadError TracedMismatches Result Source # | |
Defined in Schemas.Internal Methods throwError :: TracedMismatches -> Result a # catchError :: Result a -> (TracedMismatches -> Result a) -> Result a # | |
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 #