yaml-unscrambler-0.1.0.19: Flexible declarative YAML parsing toolkit
Safe HaskellSafe-Inferred
LanguageHaskell2010

YamlUnscrambler

Synopsis

Execution

parseText :: Value a -> Text -> Either Text a Source #

Run a value parser on strict text.

parseByteString :: Value a -> ByteString -> Either Text a Source #

Run a value parser on strict bytestring.

getExpectations :: Value a -> Value Source #

Get a tree of expectations, which can then be converted into documentation for people working with the YAML document or into one of the spec formats (e.g., YAML Spec, JSON Spec).

DSL

Value

data Value a Source #

Parser of any kind of YAML value: scalar, mapping or sequence.

Instances

Instances details
Functor Value Source # 
Instance details

Defined in YamlUnscrambler

Methods

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

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

value :: [Scalar a] -> Maybe (Mapping a) -> Maybe (Sequence a) -> Value a Source #

Specification of various alternative ways of parsing a non-nullable value.

nullableValue :: [Scalar a] -> Maybe (Mapping a) -> Maybe (Sequence a) -> Value (Maybe a) Source #

Specification of various alternative ways of parsing a nullable value.

Helpers

sequenceValue :: Sequence a -> Value a Source #

Value parser, which only expects sequence values.

mappingValue :: Mapping a -> Value a Source #

Value parser, which only expects mapping values.

scalarsValue :: [Scalar a] -> Value a Source #

Value parser, which only expects scalar values.

Scalar

data Scalar a Source #

Scalar value parser.

Instances

Instances details
Functor Scalar Source # 
Instance details

Defined in YamlUnscrambler

Methods

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

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

stringScalar :: String a -> Scalar a Source #

String scalar parser.

nullScalar :: a -> Scalar a Source #

A parser expecting a null value and resulting in the provided constant value when successful.

boolScalar :: Scalar Bool Source #

Boolean scalar parser.

scientificScalar :: Scalar Scientific Source #

Numeric scalar as scientific parser.

doubleScalar :: Scalar Double Source #

Numeric scalar as double parser.

rationalScalar :: MaxInputSize -> Scalar Rational Source #

Numeric scalar as rational parser protected with maximum allowed input size.

boundedIntegerScalar :: (Integral a, FiniteBits a) => Signed -> NumeralSystem -> Scalar a Source #

Numeric scalar parser into a bounded integer value. E.g., Int, Int64, Word, but not Integer.

unboundedIntegerScalar :: MaxInputSize -> Signed -> NumeralSystem -> Scalar Integer Source #

Numeric scalar parser into any integer value.

timestampScalar :: Scalar UTCTime Source #

String scalar parser as UTCTime in ISO-8601.

dayScalar :: Scalar Day Source #

String scalar parser as Day in ISO-8601.

timeScalar :: Scalar TimeOfDay Source #

String scalar parser as TimeOfDay in ISO-8601.

uuidScalar :: Scalar UUID Source #

String scalar parser as UUID.

binaryScalar :: Scalar ByteString Source #

String scalar parser as binary data encoded in Base-64.

Mapping

data Mapping a Source #

Mapping value parser.

Instances

Instances details
Functor Mapping Source # 
Instance details

Defined in YamlUnscrambler

Methods

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

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

foldMapping :: (key -> val -> assoc) -> Fold assoc a -> String key -> Value val -> Mapping a Source #

Mapping parser which folds pairs into some final data-structure.

byKeyMapping :: CaseSensitive -> ByKey Text a -> Mapping a Source #

Mapping parser which allows the user to look up fields and process them with individual parsers.

Sequence

data Sequence a Source #

Sequence value parser.

Instances

Instances details
Functor Sequence Source # 
Instance details

Defined in YamlUnscrambler

Methods

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

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

foldSequence :: Fold a b -> Value a -> Sequence b Source #

Homogenous sequence parser which folds into a final data-structure.

byOrderSequence :: ByOrder a -> Sequence a Source #

Heterogenous sequence parser by order in the sequence, which lets you apply individual parsers to elements.

byKeySequence :: ByKey Int a -> Sequence a Source #

Heterogenous sequence parser by index in the sequence, which lets you apply individual parsers to elements.

String

data String a Source #

String value parser applicable to string scalars and mapping keys.

Instances

Instances details
Functor String Source # 
Instance details

Defined in YamlUnscrambler

Methods

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

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

textString :: String Text Source #

String as is.

enumString :: CaseSensitive -> [(Text, a)] -> String a Source #

Look the string up as a key in the provided dictionary.

formattedString Source #

Arguments

:: Text

Format name for documentation and expectations.

-> (Text -> Either Text a) 
-> String a 

String parsed using the provided function.

attoparsedString Source #

Arguments

:: Text

Format name for documentation and expectations.

-> Parser a 
-> String a 

String parsed using the provided textual attoparsec parser.

ByKey

data ByKey key a Source #

General abstraction for specification of parsers performing lookups by keys.

Instances

Instances details
Alternative (ByKey key) Source # 
Instance details

Defined in YamlUnscrambler

Methods

empty :: ByKey key a #

(<|>) :: ByKey key a -> ByKey key a -> ByKey key a #

some :: ByKey key a -> ByKey key [a] #

many :: ByKey key a -> ByKey key [a] #

Applicative (ByKey key) Source # 
Instance details

Defined in YamlUnscrambler

Methods

pure :: a -> ByKey key a #

(<*>) :: ByKey key (a -> b) -> ByKey key a -> ByKey key b #

liftA2 :: (a -> b -> c) -> ByKey key a -> ByKey key b -> ByKey key c #

(*>) :: ByKey key a -> ByKey key b -> ByKey key b #

(<*) :: ByKey key a -> ByKey key b -> ByKey key a #

Functor (ByKey key) Source # 
Instance details

Defined in YamlUnscrambler

Methods

fmap :: (a -> b) -> ByKey key a -> ByKey key b #

(<$) :: a -> ByKey key b -> ByKey key a #

Selective (ByKey key) Source # 
Instance details

Defined in YamlUnscrambler

Methods

select :: ByKey key (Either a b) -> ByKey key (a -> b) -> ByKey key b #

atByKey :: key -> Value a -> ByKey key a Source #

Parse a value at a key using the provided parser.

atOneOfByKey :: [key] -> Value a -> ByKey key a Source #

Parse a value at one of keys (whichever exists) using the provided parser.

ByOrder

data ByOrder a Source #

Parser which fetches elements by the order in which it is composed.

Instances

Instances details
Applicative ByOrder Source # 
Instance details

Defined in YamlUnscrambler

Methods

pure :: a -> ByOrder a #

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

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

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

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

Functor ByOrder Source # 
Instance details

Defined in YamlUnscrambler

Methods

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

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

Selective ByOrder Source # 
Instance details

Defined in YamlUnscrambler

Methods

select :: ByOrder (Either a b) -> ByOrder (a -> b) -> ByOrder b #

fetchByOrder :: Value a -> ByOrder a Source #

Parse the next value using the provided parser.

Value types

newtype MaxInputSize Source #

Specification of the maximum allowed length for the input. A safety measure to ensure that the parser doesn't exhaust memory when parsing to unlimited datatypes.

Constructors

MaxInputSize Int 

newtype Signed Source #

Constructors

Signed Bool 

newtype CaseSensitive Source #

Constructors

CaseSensitive Bool