yaml-combinators-1.0: 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 # 

Methods

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

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

Monoid (Parser a) Source # 

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

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.

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)

data FieldParser a Source #

A FieldParser describes how to parse an object.

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.

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)

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 

data Reason Source #

Describes what exactly went wrong during parsing.

Instances

Orphan instances

Generic Value Source # 

Associated Types

type Code Value :: [[*]] #

Methods

from :: Value -> Rep Value #

to :: Rep Value -> Value #

HasDatatypeInfo Value Source # 

Methods

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