yamlparse-applicative-0.0.0.0

Safe HaskellNone
LanguageHaskell2010

YamlParse.Applicative.Class

Synopsis

Documentation

class YamlSchema a where Source #

A class of types for which a schema is defined.

Note that you do not have to use this class and can just use your own parser values. Note also that the parsing of a type of this class should correspond to the parsing of the type in the FromJSON class.

Minimal complete definition

yamlSchema

Methods

yamlSchema :: YamlParser a Source #

A yamlschema for one value

See the sections on helper functions for implementing this for plenty of examples.

yamlSchemaList :: YamlParser [a] Source #

A yamlschema for a list of values

This is really only useful for cases like Char and String

requiredField :: YamlSchema a => Text -> Text -> ObjectParser a Source #

A parser for a required field in an object at a given key

requiredField' :: YamlSchema a => Text -> ObjectParser a Source #

A parser for a required field in an object at a given key without a help text

optionalField :: YamlSchema a => Text -> Text -> ObjectParser (Maybe a) Source #

A parser for an optional field in an object at a given key

optionalField' :: YamlSchema a => Text -> ObjectParser (Maybe a) Source #

A parser for an optional field in an object at a given key without a help text

optionalFieldWithDefault :: (Show a, YamlSchema a) => Text -> a -> Text -> ObjectParser a Source #

A parser for an optional field in an object at a given key with a default value

optionalFieldWithDefault' :: (Show a, YamlSchema a) => Text -> a -> ObjectParser a Source #

A parser for an optional field in an object at a given key with a default value without a help text

viaYamlSchema :: YamlSchema a => Value -> Parser a Source #

Helper function to implement FromJSON via YamlSchema

Example:

instance FromJSON Config where
  parseJSON = viaYamlSchema

newtype ViaYamlSchema a Source #

A helper newtype to parse a yaml value using the YamlSchema parser.

Example:

case Data.Yaml.decodeEither' contents of
  Left e -> die $ show e
  Right (ViaYamlSchema res) -> print res

This only helps you when you really don't want to implement a FromJSON instance. See viaYamlSchema if you do.

Constructors

ViaYamlSchema a 
Instances
Eq a => Eq (ViaYamlSchema a) Source # 
Instance details

Defined in YamlParse.Applicative.Class

Show a => Show (ViaYamlSchema a) Source # 
Instance details

Defined in YamlParse.Applicative.Class

Generic (ViaYamlSchema a) Source # 
Instance details

Defined in YamlParse.Applicative.Class

Associated Types

type Rep (ViaYamlSchema a) :: Type -> Type #

YamlSchema a => FromJSON (ViaYamlSchema a) Source # 
Instance details

Defined in YamlParse.Applicative.Class

type Rep (ViaYamlSchema a) Source # 
Instance details

Defined in YamlParse.Applicative.Class

type Rep (ViaYamlSchema a) = D1 (MetaData "ViaYamlSchema" "YamlParse.Applicative.Class" "yamlparse-applicative-0.0.0.0-5kyh1tPTqvuDc28BfAkr0m" True) (C1 (MetaCons "ViaYamlSchema" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))