HsYAML-0.1.2.0: Pure Haskell YAML 1.2 parser

Copyright© Herbert Valerio Riedel 2015-2018
LicenseGPL-2.0-or-later
Safe HaskellSafe
LanguageHaskell2010

Data.YAML

Contents

Description

Document oriented YAML parsing API inspired by aeson.

Overview

The diagram below depicts the standard layers of a YAML 1.2 processor. This module covers the upper Native and Representation layers, whereas the Data.YAML.Event and Data.YAML.Token modules provide access to the lower Serialization and Presentation layers respectively.

Quick Start Tutorial

Let's assume we want to decode (i.e. load) a simple YAML document

- name: Erik Weisz
  age: 52
  magic: True
- name: Mina Crandon
  age: 53

into a native Haskell data structure of type [Person], i.e. a list of Person records.

The code below shows how to manually define a Person record type together with a FromYAML instance:

{-# LANGUAGE OverloadedStrings #-}

import Data.YAML

data Person = Person
    { name  :: Text
    , age   :: Int
    , magic :: Bool
    } deriving Show

instance FromYAML Person where
   parseYAML = withMap "Person" $ \m -> Person
       <$> m .: "name"
       <*> m .: "age"
       <*> m .:? "magic" .!= False

And now we can decode the YAML document like so:

>>> decode "- name: Erik Weisz\n  age: 52\n  magic: True\n- name: Mina Crandon\n  age: 53" :: Either String [[Person]]
Right [[Person {name = "Erik Weisz", age = 52, magic = True},Person {name = "Mina Crandon", age = 53, magic = False}]]
Synopsis

Typeclass-based resolving/decoding

decode :: FromYAML v => ByteString -> Either String [v] Source #

Decode YAML document(s) using the YAML 1.2 Core schema

Each document contained in the YAML stream produce one element of the response list. Here's an example of decoding two concatenated YAML documents:

>>> decode "Foo\n---\nBar" :: Either String [Text]
Right ["Foo","Bar"]

Note that an empty stream doesn't contain any (non-comment) document nodes, and therefore results in an empty result list:

>>> decode "# just a comment" :: Either String [Text]
Right []

decode uses the same settings as decodeNode for tag-resolving. If you need a different custom parsing configuration, you need to combine parseEither and decodeNode' yourself.

The decode as well as the decodeNode functions supports decoding from YAML streams using the UTF-8, UTF-16 (LE or BE), or UTF-32 (LE or BE) encoding (which is auto-detected).

decode1 :: FromYAML v => ByteString -> Either String v Source #

Convenience wrapper over decode expecting exactly one YAML document

>>> decode1 "---\nBar\n..." :: Either String Text
Right "Bar"
>>> decode1 "Foo\n---\nBar" :: Either String Text
Left "unexpected multiple YAML documents"
>>> decode1 "# Just a comment" :: Either String Text
Left "empty YAML stream"

Since: 0.1.2.0

decodeStrict :: FromYAML v => ByteString -> Either String [v] Source #

Like decode but takes a strict ByteString

Since: 0.1.1.0

decode1Strict :: FromYAML v => ByteString -> Either String v Source #

Like decode1 but takes a strict ByteString

Since: 0.1.2.0

class FromYAML a where Source #

A type into which YAML nodes can be converted/deserialized

Methods

parseYAML :: Node -> Parser a Source #

Instances
FromYAML Bool Source # 
Instance details

Defined in Data.YAML

FromYAML Double Source # 
Instance details

Defined in Data.YAML

FromYAML Int Source # 
Instance details

Defined in Data.YAML

FromYAML Int8 Source # 
Instance details

Defined in Data.YAML

FromYAML Int16 Source # 
Instance details

Defined in Data.YAML

FromYAML Int32 Source # 
Instance details

Defined in Data.YAML

FromYAML Int64 Source # 
Instance details

Defined in Data.YAML

FromYAML Integer Source # 
Instance details

Defined in Data.YAML

FromYAML Natural Source #

Since: 0.1.0.0

Instance details

Defined in Data.YAML

FromYAML Word Source # 
Instance details

Defined in Data.YAML

FromYAML Word8 Source # 
Instance details

Defined in Data.YAML

FromYAML Word16 Source # 
Instance details

Defined in Data.YAML

FromYAML Word32 Source # 
Instance details

Defined in Data.YAML

FromYAML Word64 Source # 
Instance details

Defined in Data.YAML

FromYAML Text Source # 
Instance details

Defined in Data.YAML

FromYAML Node Source #

Trivial instance

Instance details

Defined in Data.YAML

FromYAML v => FromYAML [v] Source # 
Instance details

Defined in Data.YAML

Methods

parseYAML :: Node -> Parser [v] Source #

FromYAML a => FromYAML (Maybe a) Source # 
Instance details

Defined in Data.YAML

Methods

parseYAML :: Node -> Parser (Maybe a) Source #

(FromYAML a, FromYAML b) => FromYAML (a, b) Source # 
Instance details

Defined in Data.YAML

Methods

parseYAML :: Node -> Parser (a, b) Source #

(Ord k, FromYAML k, FromYAML v) => FromYAML (Map k v) Source # 
Instance details

Defined in Data.YAML

Methods

parseYAML :: Node -> Parser (Map k v) Source #

(FromYAML a, FromYAML b, FromYAML c) => FromYAML (a, b, c) Source # 
Instance details

Defined in Data.YAML

Methods

parseYAML :: Node -> Parser (a, b, c) Source #

(FromYAML a, FromYAML b, FromYAML c, FromYAML d) => FromYAML (a, b, c, d) Source # 
Instance details

Defined in Data.YAML

Methods

parseYAML :: Node -> Parser (a, b, c, d) Source #

(FromYAML a, FromYAML b, FromYAML c, FromYAML d, FromYAML e) => FromYAML (a, b, c, d, e) Source # 
Instance details

Defined in Data.YAML

Methods

parseYAML :: Node -> Parser (a, b, c, d, e) Source #

(FromYAML a, FromYAML b, FromYAML c, FromYAML d, FromYAML e, FromYAML f) => FromYAML (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.YAML

Methods

parseYAML :: Node -> Parser (a, b, c, d, e, f) Source #

(FromYAML a, FromYAML b, FromYAML c, FromYAML d, FromYAML e, FromYAML f, FromYAML g) => FromYAML (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Data.YAML

Methods

parseYAML :: Node -> Parser (a, b, c, d, e, f, g) Source #

data Parser a Source #

YAML Parser Monad used by FromYAML

See also parseEither or decode

Instances
Monad Parser Source # 
Instance details

Defined in Data.YAML

Methods

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

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

return :: a -> Parser a #

fail :: String -> Parser a #

Functor Parser Source # 
Instance details

Defined in Data.YAML

Methods

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

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

MonadFail Parser Source #

Since: 0.1.1.0

Instance details

Defined in Data.YAML

Methods

fail :: String -> Parser a #

Applicative Parser Source # 
Instance details

Defined in Data.YAML

Methods

pure :: a -> Parser a #

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

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

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

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

Alternative Parser Source #

Since: 0.1.1.0

Instance details

Defined in Data.YAML

Methods

empty :: Parser a #

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

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

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

MonadPlus Parser Source #

Since: 0.1.1.0

Instance details

Defined in Data.YAML

Methods

mzero :: Parser a #

mplus :: Parser a -> Parser a -> Parser a #

parseEither :: Parser a -> Either String a Source #

Run Parser

A common use-case is parseEither parseYAML.

typeMismatch Source #

Arguments

:: String

descriptive name of expected data

-> Node

actual node

-> Parser a 

Informative failure helper

This is typically used in fall-through cases of parseYAML like so

instance FromYAML ... where
  parseYAML ...  = ...
  parseYAML node = typeMismatch "SomeThing" node

Since: 0.1.1.0

Accessors for YAML Nodes

type Mapping = Map Node Node Source #

YAML mapping

(.:) :: FromYAML a => Mapping -> Text -> Parser a Source #

Retrieve value in Node indexed by a !!str Text key.

This parser fails if the key doesn't exist.

(.:?) :: FromYAML a => Mapping -> Text -> Parser (Maybe a) Source #

Retrieve optional value in Node indexed by a !!str Text key.

Nothing is returned if the key is missing or points to a tag:yaml.org,2002:null node. This combinator only fails if the key exists but cannot be converted to the required type.

See also .:!.

(.:!) :: FromYAML a => Mapping -> Text -> Parser (Maybe a) Source #

Retrieve optional value in Node indexed by a !!str Text key.

Nothing is returned if the key is missing. This combinator only fails if the key exists but cannot be converted to the required type.

NOTE: This is a variant of .:? which doesn't map a tag:yaml.org,2002:null node to Nothing.

(.!=) :: Parser (Maybe a) -> a -> Parser a Source #

Defaulting helper to be used with .:? or .:!.

Prism-style parsers

withSeq :: String -> ([Node] -> Parser a) -> Node -> Parser a Source #

Operate on tag:yaml.org,2002:seq node (or fail)

withBool :: String -> (Bool -> Parser a) -> Node -> Parser a Source #

Operate on tag:yaml.org,2002:bool node (or fail)

withFloat :: String -> (Double -> Parser a) -> Node -> Parser a Source #

Operate on tag:yaml.org,2002:float node (or fail)

withInt :: String -> (Integer -> Parser a) -> Node -> Parser a Source #

Operate on tag:yaml.org,2002:int node (or fail)

withNull :: String -> Parser a -> Node -> Parser a Source #

Operate on tag:yaml.org,2002:null node (or fail)

withStr :: String -> (Text -> Parser a) -> Node -> Parser a Source #

Operate on tag:yaml.org,2002:str node (or fail)

withMap :: String -> (Mapping -> Parser a) -> Node -> Parser a Source #

Operate on tag:yaml.org,2002:seq node (or fail)

"Concrete" AST

decodeNode :: ByteString -> Either String [Doc Node] Source #

Parse and decode YAML document(s) into Node graphs

This is a convenience wrapper over decodeNode'

decodeNode = decodeNode' coreSchemaResolver False False

In other words,

  • Use the YAML 1.2 Core schema for resolving
  • Don't create Anchor nodes
  • Disallow cyclic anchor references

decodeNode' Source #

Arguments

:: SchemaResolver

YAML Schema resolver to use

-> Bool

Whether to emit anchor nodes

-> Bool

Whether to allow cyclic references

-> ByteString

YAML document to parse

-> Either String [Doc Node] 

Customizable variant of decodeNode

newtype Doc n Source #

YAML Document tree/graph

Constructors

Doc n 
Instances
Eq n => Eq (Doc n) Source # 
Instance details

Defined in Data.YAML

Methods

(==) :: Doc n -> Doc n -> Bool #

(/=) :: Doc n -> Doc n -> Bool #

Ord n => Ord (Doc n) Source # 
Instance details

Defined in Data.YAML

Methods

compare :: Doc n -> Doc n -> Ordering #

(<) :: Doc n -> Doc n -> Bool #

(<=) :: Doc n -> Doc n -> Bool #

(>) :: Doc n -> Doc n -> Bool #

(>=) :: Doc n -> Doc n -> Bool #

max :: Doc n -> Doc n -> Doc n #

min :: Doc n -> Doc n -> Doc n #

Show n => Show (Doc n) Source # 
Instance details

Defined in Data.YAML

Methods

showsPrec :: Int -> Doc n -> ShowS #

show :: Doc n -> String #

showList :: [Doc n] -> ShowS #

data Node Source #

YAML Document node

Instances
Eq Node Source # 
Instance details

Defined in Data.YAML

Methods

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

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

Ord Node Source # 
Instance details

Defined in Data.YAML

Methods

compare :: Node -> Node -> Ordering #

(<) :: Node -> Node -> Bool #

(<=) :: Node -> Node -> Bool #

(>) :: Node -> Node -> Bool #

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

max :: Node -> Node -> Node #

min :: Node -> Node -> Node #

Show Node Source # 
Instance details

Defined in Data.YAML

Methods

showsPrec :: Int -> Node -> ShowS #

show :: Node -> String #

showList :: [Node] -> ShowS #

FromYAML Node Source #

Trivial instance

Instance details

Defined in Data.YAML

data Scalar Source #

Primitive scalar types as defined in YAML 1.2

Constructors

SNull
tag:yaml.org,2002:null
SBool !Bool
tag:yaml.org,2002:bool
SFloat !Double
tag:yaml.org,2002:float
SInt !Integer
tag:yaml.org,2002:int
SStr !Text
tag:yaml.org,2002:str
SUnknown !Tag !Text

unknown/unsupported tag or untagged (thus unresolved) scalar

Instances
Eq Scalar Source # 
Instance details

Defined in Data.YAML.Schema

Methods

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

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

Ord Scalar Source # 
Instance details

Defined in Data.YAML.Schema

Show Scalar Source # 
Instance details

Defined in Data.YAML.Schema

YAML 1.2 Schema resolvers

data SchemaResolver Source #

Definition of a YAML 1.2 Schema

A YAML schema defines how implicit tags are resolved to concrete tags and how data is represented textually in YAML.

jsonSchemaResolver :: SchemaResolver Source #

Strict JSON schema resolver as specified in YAML 1.2 / 10.2.2. Tag Resolution

Generalised AST construction

decodeLoader :: forall n m. MonadFix m => Loader m n -> ByteString -> m (Either String [n]) Source #

Generalised document tree/graph construction

This doesn't yet perform any tag resolution (thus all scalars are represented as Text values). See also decodeNode for a more convenient interface.

data Loader m n Source #

Structure defining how to construct a document tree/graph

Constructors

Loader 

Fields

type NodeId = Word Source #

Unique identifier for identifying nodes

This is allows to observe the alias/anchor-reference structure