yaml-combinators-1.1.2: YAML parsing combinators for improved validation and error reporting

Safe HaskellNone
LanguageHaskell2010

Data.Yaml.Combinators

Contents

Description

Combinators for parsing YAML into Haskell types.

Based on the article Better Yaml Parsing.

Synopsis

Documentation

data Parser a Source #

A top-level YAML parser.

Instances
Functor Parser Source # 
Instance details

Defined in Data.Yaml.Combinators

Methods

fmap :: (a -> b) -> Parser a -> Parser b #

(<$) :: a -> Parser b -> Parser a #

Semigroup (Parser a) Source # 
Instance details

Defined in Data.Yaml.Combinators

Methods

(<>) :: Parser a -> Parser a -> Parser a #

sconcat :: NonEmpty (Parser a) -> Parser a #

stimes :: Integral b => b -> Parser a -> Parser a #

Monoid (Parser a) Source # 
Instance details

Defined in Data.Yaml.Combinators

Methods

mempty :: Parser a #

mappend :: Parser a -> Parser a -> Parser a #

mconcat :: [Parser a] -> Parser a #

parse :: Parser a -> ByteString -> Either String a Source #

Run a Parser on a ByteString containing the YAML content.

This is a high-level function implemented on top of runParser.

runParser :: Parser a -> Value -> Either ParseError a Source #

A low-level function to run a Parser.

Scalars

string :: Parser Text Source #

Match a single YAML string.

>>> parse string "howdy"
Right "howdy"

theString :: Text -> Parser () Source #

Match a specific YAML string, usually a «tag» identifying a particular form of an array or object.

>>> parse (theString "hello") "hello"
Right ()
>>> either putStr print $ parse (theString "hello") "bye"
Expected "hello" instead of:

bye

number :: Parser Scientific Source #

Match a real number.

>>> parse number "3.14159"
Right 3.14159

integer :: (Integral i, Bounded i) => Parser i Source #

Match an integer.

>>> parse (integer @Int) "2017"
Right 2017

bool :: Parser Bool Source #

Match a boolean.

>>> parse bool "yes"
Right True

null_ :: Parser () Source #

Match the null value.

>>> parse null_ "null"
Right ()

Since: 1.1

Arrays

array :: Parser a -> Parser (Vector a) Source #

Match an array of elements, where each of elements are matched by the same parser. This is the function you'll use most of the time when parsing arrays, as they are usually homogeneous.

>>> parse (array string) "[a,b,c]"
Right ["a","b","c"]

theArray :: ElementParser a -> Parser a Source #

Match an array consisting of a fixed number of elements. The way each element is parsed depends on its position within the array and is determined by the ElementParser.

>>> parse (theArray $ (,) <$> element string <*> element bool) "[f, true]"
Right ("f",True)

data ElementParser a Source #

An ElementParser describes how to parse a fixed-size array where each positional element has its own parser.

This can be used to parse heterogeneous tuples represented as YAML arrays.

Instances
Functor ElementParser Source # 
Instance details

Defined in Data.Yaml.Combinators

Methods

fmap :: (a -> b) -> ElementParser a -> ElementParser b #

(<$) :: a -> ElementParser b -> ElementParser a #

Applicative ElementParser Source # 
Instance details

Defined in Data.Yaml.Combinators

element :: Parser a -> ElementParser a Source #

Construct an ElementParser that parses the current array element with the given Parser.

Objects

object :: FieldParser a -> Parser a Source #

Match an object. Which set of keys to expect and how their values should be parsed is determined by the FieldParser.

>>> let p = object $ (,) <$> field "name" string <*> optField "age" (integer @Int)
>>> parse p "{ name: Anton, age: 2 }"
Right ("Anton",Just 2)
>>> parse p "name: Roma"
Right ("Roma",Nothing)

By default, this function will fail when there are unrecognized fields in the object. See extraFields for a way to capture or ignore them.

data FieldParser a Source #

A FieldParser describes how to parse an object.

Instances
Functor FieldParser Source # 
Instance details

Defined in Data.Yaml.Combinators

Methods

fmap :: (a -> b) -> FieldParser a -> FieldParser b #

(<$) :: a -> FieldParser b -> FieldParser a #

Applicative FieldParser Source # 
Instance details

Defined in Data.Yaml.Combinators

Methods

pure :: a -> FieldParser a #

(<*>) :: FieldParser (a -> b) -> FieldParser a -> FieldParser b #

liftA2 :: (a -> b -> c) -> FieldParser a -> FieldParser b -> FieldParser c #

(*>) :: FieldParser a -> FieldParser b -> FieldParser b #

(<*) :: FieldParser a -> FieldParser b -> FieldParser a #

field Source #

Arguments

:: Text

field name

-> Parser a

value parser

-> FieldParser a 

Require an object field with the given name and with a value matched by the given Parser.

optField Source #

Arguments

:: Text

field name

-> Parser a

value parser

-> FieldParser (Maybe a) 

Declare an optional object field with the given name and with a value matched by the given Parser.

defaultField Source #

Arguments

:: Text

field name

-> a

default value

-> Parser a

value parser

-> FieldParser a 

Declare an optional object field with the given name and with a default to use if the field is absent.

theField Source #

Arguments

:: Text

key name

-> Text

expected value

-> FieldParser () 

Require an object field with the given name and the given string value.

This is a convenient wrapper around theString intended for «tagging» objects.

>>> :{
    let p = object (Right <$ theField "type" "number" <*> field "value" number)
         <> object (Left  <$ theField "type" "string" <*> field "value" string)
>>> :}
>>> parse p "{type: string, value: abc}"
Right (Left "abc")
>>> parse p "{type: number, value: 123}"
Right (Right 123.0)

extraFields :: FieldParser Object Source #

This combinator does two things:

  1. Allow extra fields (not specified by field, theField etc.) in the parsed object.
  2. Return such extra fields as an Value.

The return value can be of course ignored.

>>> let fp = field "name" string
>>> either putStr print $ parse (object fp) "name: Anton"
"Anton"
>>> either putStr print $ parse (object fp) "{name: Anton, age: 2}"
Unexpected

age: 2

as part of

age: 2
name: Anton
>>> either putStr print $ parse (object $ (,) <$> fp <*> extraFields) "{name: Anton, age: 2}"
("Anton",fromList [("age",Number 2.0)])
>>> either putStr print $ parse (object $ fp <* extraFields) "{name: Anton, age: 2}"
"Anton"

Since: 1.1.2

Arbitrary values

anyValue :: Parser Value Source #

Match any JSON value and return it as Aeson's Value.

>>> parse anyValue "[one, two, {three: four}]"
Right (Array [String "one",String "two",Object (fromList [("three",String "four")])])

Since: 1.1.1

Errors

data ParseError Source #

A parse error. Reason describes the error. The Int field denotes at which level the error occurred and is used to select the deepest (most relevant) error when merging multiple parsers.

Constructors

ParseError !Int Reason 
Instances
Eq ParseError Source # 
Instance details

Defined in Data.Yaml.Combinators

Show ParseError Source # 
Instance details

Defined in Data.Yaml.Combinators

ppParseError :: ParseError -> String Source #

Pretty-print a ParseError

Since: 1.1

data Reason Source #

Describes what exactly went wrong during parsing.

Instances
Eq Reason Source # 
Instance details

Defined in Data.Yaml.Combinators

Methods

(==) :: Reason -> Reason -> Bool #

(/=) :: Reason -> Reason -> Bool #

Show Reason Source # 
Instance details

Defined in Data.Yaml.Combinators

validate Source #

Arguments

:: Parser a

parser to wrap

-> (a -> Either String b)

validator

-> Parser b 

Make a parser match only valid values.

If the validator does not accept the value, it should return a Left String with a noun phrase that characterizes the expected value, as in the example:

>>> let acceptEven n = if even n then Right n else Left "an even number"
>>> either putStr print $ parse (integer @Int `validate` acceptEven) "2017"
Expected an even number instead of:

2017

Since: 1.0.1

Orphan instances

Generic Value Source # 
Instance details

Associated Types

type Code Value :: [[Type]] #

Methods

from :: Value -> Rep Value #

to :: Rep Value -> Value #

HasDatatypeInfo Value Source # 
Instance details

Associated Types

type DatatypeInfoOf Value :: DatatypeInfo #

Methods

datatypeInfo :: proxy Value -> DatatypeInfo (Code Value) #