HsYAML-0.2.1.0: Pure Haskell YAML 1.2 processor

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.

Synopsis

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

This section contains basic information on the different ways to work with YAML data using this library.

Decoding/Loading YAML document

We address the process of loading data from a YAML document as decoding.

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 (Pos,String) [[Person]]
Right [[Person {name = "Erik Weisz", age = 52, magic = True},Person {name = "Mina Crandon", age = 53, magic = False}]]

There are predefined FromYAML instance for many types.

The example below shows decoding multiple YAML documents into a list of Int lists:

>>> decode "---\n- 1\n- 2\n- 3\n---\n- 4\n- 5\n- 6" :: Either (Pos,String) [[Int]]
Right [[1,2,3],[4,5,6]]

If you are expecting exactly one YAML document then you can use convenience function decode1

>>> decode1 "- 1\n- 2\n- 3\n" :: Either (Pos,String) [Int]
Right [1,2,3]

Working with AST

Sometimes we want to work with YAML data directly, without first converting it to a custom data type.

We can easily do that by using the Node type, which is an instance of FromYAML, is used to represent an arbitrary YAML AST (abstract syntax tree). For example,

>>> decode1 "Name: Vijay" :: Either (Pos,String) (Node Pos)
Right (Mapping (Pos {posByteOffset = 0, posCharOffset = 0, posLine = 1, posColumn = 0}) Just "tag:yaml.org,2002:map" (fromList [(Scalar (Pos {posByteOffset = 0, posCharOffset = 0, posLine = 1, posColumn = 0}) (SStr "Name"),Scalar (Pos {posByteOffset = 6, posCharOffset = 6, posLine = 1, posColumn = 6}) (SStr "Vijay"))]))

The type parameter Pos is used to indicate the position of each YAML Node in the document. So using the Node type we can easily decode any YAML document.

Pretty-printing source locations

Syntax errors or even conversion errors are reported with a source location, e.g.

>>> decode "- name: Erik Weisz\n  age: 52\n  magic: True\n- name: Mina Crandon\n  age: young" :: Either (Pos,String) [[Person]]
Left (Pos {posByteOffset = 71, posCharOffset = 71, posLine = 5, posColumn = 7},"expected !!int instead of !!str")

While accurate this isn't a very convenient error representation. Instead we can use the prettyPosWithSource helper function to create more convenient error report like so

readPersons :: FilePath -> IO [Person]
readPersons fname = do
   raw <- BS.L.readFile fname
   case decode1 raw of
     Left (loc,emsg) -> do
       hPutStrLn stderr (fname ++ ":" ++ prettyPosWithSource loc raw " error" ++ emsg)
       pure []
     Right persons -> pure persons

which will then print errors in a common form such as

people.yaml:5:7: error
   |
 5 |   age: young
   |        ^
expected !!int instead of !!str

Encoding/dumping

We address the process of dumping information from a Haskell-data type(s) to a YAML document(s) as encoding.

Suppose we want to encode a Haskell-data type Person

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

To encode data, we need to define a ToYAML instance.

instance ToYAML Person where
    -- this generates a Node
    toYAML (Person n a) = mapping [ "name" .= n, "age" .= a]

We can now encode a node like so:

>>> encode [Person {name = "Vijay", age = 19}]
"age: 19\nname: Vijay\n"

There are predefined ToYAML instances for many types. Here's an example encoding a complex Haskell Node'

>>> encode1 $ toYAML ([1,2,3], Map.fromList [(1, 2)])
"- - 1\n  - 2\n  - 3\n- 1: 2\n"

Typeclass-based resolving/decoding

decode :: FromYAML v => ByteString -> Either (Pos, 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 (Pos,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 (Pos,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).

Since: 0.2.0

decode1 :: FromYAML v => ByteString -> Either (Pos, String) v Source #

Convenience wrapper over decode expecting exactly one YAML document

>>> decode1 "---\nBar\n..." :: Either (Pos,String) Text
Right "Bar"
>>> decode1 "Foo\n---\nBar" :: Either (Pos,String) Text
Left (Pos {posByteOffset = 8, posCharOffset = 8, posLine = 3, posColumn = 0},"unexpected multiple YAML documents")
>>> decode1 "# Just a comment" :: Either (Pos,String) Text
Left (Pos {posByteOffset = 0, posCharOffset = 0, posLine = 1, posColumn = 0},"empty YAML stream")

Since: 0.2.0

decodeStrict :: FromYAML v => ByteString -> Either (Pos, String) [v] Source #

Like decode but takes a strict ByteString

Since: 0.2.0

decode1Strict :: FromYAML v => ByteString -> Either (Pos, String) v Source #

Like decode1 but takes a strict ByteString

Since: 0.2.0

class FromYAML a where Source #

A type into which YAML nodes can be converted/deserialized

Methods

parseYAML :: Node Pos -> 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.1.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 Scalar Source #

Since: 0.2.1

Instance details

Defined in Data.YAML

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

Defined in Data.YAML

Methods

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

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

Defined in Data.YAML

Methods

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

loc ~ Pos => FromYAML (Node loc) Source #

Trivial instance

Instance details

Defined in Data.YAML

Methods

parseYAML :: Node Pos -> Parser (Node loc) Source #

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

Defined in Data.YAML

Methods

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

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

Defined in Data.YAML

Methods

parseYAML :: Node Pos -> 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 Pos -> 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 Pos -> 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 Pos -> 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 Pos -> 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 Pos -> 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 #

NOTE: fail doesn't convey proper position information unless used within the with*-style helpers; consequently it's recommended to use failAtNode when not covered by the location scope of a with*-style combinator.

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 (Pos, String) a Source #

Run Parser

A common use-case is parseEither parseYAML.

failAtNode :: Node Pos -> String -> Parser a Source #

Trigger parsing failure located at a specific Node

Since: 0.2.0.0

typeMismatch Source #

Arguments

:: String

descriptive name of expected data

-> Node Pos

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 tMappings

type Mapping loc = Map (Node loc) (Node loc) Source #

YAML mapping

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

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

This parser fails if the key doesn't exist.

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

Retrieve optional value in tMapping 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 Pos -> Text -> Parser (Maybe a) Source #

Retrieve optional value in tMapping 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 .:!.

Typeclass-based dumping

encode :: ToYAML v => [v] -> ByteString Source #

Serialize YAML Node(s) using the YAML 1.2 Core schema to a lazy UTF8 encoded ByteString.

Each YAML Node produces exactly one YAML Document.

Here is an example of encoding a list of strings to produce a list of YAML Documents

>>> encode (["Document 1", "Document 2"] :: [Text])
"Document 1\n...\nDocument 2\n"

If we treat the above list of strings as a single sequence then we will produce a single YAML Document having a single sequence.

>>> encode ([["Document 1", "Document 2"]] :: [[Text]])
"- Document 1\n- Document 2\n"

Alternatively, if you only need a single YAML document in a YAML stream you might want to use the convenience function encode1; or, if you need more control over the encoding, see encodeNode'.

Since: 0.2.0

encode1 :: ToYAML v => v -> ByteString Source #

Convenience wrapper over encode taking exactly one YAML Node. Hence it will always output exactly one YAML Document

Here is example of encoding a list of strings to produce exactly one of YAML Documents

>>> encode1 (["Document 1", "Document 2"] :: [Text])
"- Document 1\n- Document 2\n"

Since: 0.2.0

encodeStrict :: ToYAML v => [v] -> ByteString Source #

Like encode but outputs ByteString

Since: 0.2.0

encode1Strict :: ToYAML v => v -> ByteString Source #

Like encode1 but outputs a strict ByteString

Since: 0.2.0

class ToYAML a where Source #

A type from which YAML nodes can be constructed

Since: 0.2.0.0

Methods

toYAML :: a -> Node () Source #

Convert a Haskell Data-type to a YAML Node data type.

Instances
ToYAML Bool Source # 
Instance details

Defined in Data.YAML

Methods

toYAML :: Bool -> Node () Source #

ToYAML Double Source # 
Instance details

Defined in Data.YAML

Methods

toYAML :: Double -> Node () Source #

ToYAML Int Source # 
Instance details

Defined in Data.YAML

Methods

toYAML :: Int -> Node () Source #

ToYAML Int8 Source # 
Instance details

Defined in Data.YAML

Methods

toYAML :: Int8 -> Node () Source #

ToYAML Int16 Source # 
Instance details

Defined in Data.YAML

Methods

toYAML :: Int16 -> Node () Source #

ToYAML Int32 Source # 
Instance details

Defined in Data.YAML

Methods

toYAML :: Int32 -> Node () Source #

ToYAML Int64 Source # 
Instance details

Defined in Data.YAML

Methods

toYAML :: Int64 -> Node () Source #

ToYAML Integer Source # 
Instance details

Defined in Data.YAML

Methods

toYAML :: Integer -> Node () Source #

ToYAML Natural Source # 
Instance details

Defined in Data.YAML

Methods

toYAML :: Natural -> Node () Source #

ToYAML Word Source # 
Instance details

Defined in Data.YAML

Methods

toYAML :: Word -> Node () Source #

ToYAML Word8 Source # 
Instance details

Defined in Data.YAML

Methods

toYAML :: Word8 -> Node () Source #

ToYAML Word16 Source # 
Instance details

Defined in Data.YAML

Methods

toYAML :: Word16 -> Node () Source #

ToYAML Word32 Source # 
Instance details

Defined in Data.YAML

Methods

toYAML :: Word32 -> Node () Source #

ToYAML Word64 Source # 
Instance details

Defined in Data.YAML

Methods

toYAML :: Word64 -> Node () Source #

ToYAML Text Source # 
Instance details

Defined in Data.YAML

Methods

toYAML :: Text -> Node () Source #

ToYAML Scalar Source #

Since: 0.2.1

Instance details

Defined in Data.YAML

Methods

toYAML :: Scalar -> Node () Source #

ToYAML a => ToYAML [a] Source # 
Instance details

Defined in Data.YAML

Methods

toYAML :: [a] -> Node () Source #

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

Defined in Data.YAML

Methods

toYAML :: Maybe a -> Node () Source #

Loc loc => ToYAML (Node loc) Source # 
Instance details

Defined in Data.YAML

Methods

toYAML :: Node loc -> Node () Source #

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

Defined in Data.YAML

Methods

toYAML :: (a, b) -> Node () Source #

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

Defined in Data.YAML

Methods

toYAML :: Map k v -> Node () Source #

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

Defined in Data.YAML

Methods

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

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

Defined in Data.YAML

Methods

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

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

Defined in Data.YAML

Methods

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

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

Defined in Data.YAML

Methods

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

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

Defined in Data.YAML

Methods

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

Accessors for encoding tMappings

type Pair = (Node (), Node ()) Source #

Represents a key-value pair in YAML tMappings

See also .= and mapping

Since: 0.2.1

mapping :: [Pair] -> Node () Source #

Since: 0.2.0

(.=) :: ToYAML a => Text -> a -> Pair Source #

Since: 0.2.0

Prism-style parsers

withScalar :: String -> (Scalar -> Parser a) -> Node Pos -> Parser a Source #

Operate on tNode node (or fail)

Since: 0.2.1

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

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

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

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

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

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

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

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

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

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

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

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

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

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

"Concrete" AST

decodeNode :: ByteString -> Either (Pos, String) [Doc (Node Pos)] Source #

Parse and decode YAML document(s) into Node graphs

This is a convenience wrapper over decodeNode', i.e.

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

Since: 0.2.0

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 (Pos, String) [Doc (Node Pos)] 

Customizable variant of decodeNode

Since: 0.2.0

encodeNode :: [Doc (Node ())] -> ByteString Source #

Dump YAML Nodes as a lazy UTF8 encoded ByteString

Each YAML Node is emitted as a individual YAML Document where each Document is terminated by a DocumentEnd indicator.

This is a convenience wrapper over encodeNode'

Since: 0.2.0

encodeNode' :: SchemaEncoder -> Encoding -> [Doc (Node ())] -> ByteString Source #

Customizable variant of encodeNode

NOTE: A leading BOM will be emitted for all encodings other than UTF8.

Since: 0.2.0

newtype Doc n Source #

YAML Document tree/graph

NOTE: In future versions of this API meta-data about the YAML document might be included as additional fields inside Doc

Constructors

Doc 

Fields

Instances
Functor Doc Source #

Since: 0.2.1

Instance details

Defined in Data.YAML.Internal

Methods

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

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

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

Defined in Data.YAML.Internal

Methods

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

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

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

Defined in Data.YAML.Internal

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.Internal

Methods

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

show :: Doc n -> String #

showList :: [Doc n] -> ShowS #

Generic (Doc n) Source # 
Instance details

Defined in Data.YAML.Internal

Associated Types

type Rep (Doc n) :: Type -> Type #

Methods

from :: Doc n -> Rep (Doc n) x #

to :: Rep (Doc n) x -> Doc n #

NFData n => NFData (Doc n) Source #

Since: 0.2.0

Instance details

Defined in Data.YAML.Internal

Methods

rnf :: Doc n -> () #

type Rep (Doc n) Source # 
Instance details

Defined in Data.YAML.Internal

type Rep (Doc n) = D1 (MetaData "Doc" "Data.YAML.Internal" "HsYAML-0.2.1.0-3n04Fs6nDN3CMPVb0vyYIF" True) (C1 (MetaCons "Doc" PrefixI True) (S1 (MetaSel (Just "docRoot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 n)))

data Node loc Source #

YAML Document node

Since: 0.2.0

Constructors

Scalar !loc !Scalar 
Mapping !loc !Tag (Mapping loc) 
Sequence !loc !Tag [Node loc] 
Anchor !loc !NodeId !(Node loc) 
Instances
Functor Node Source # 
Instance details

Defined in Data.YAML.Internal

Methods

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

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

Eq (Node loc) Source # 
Instance details

Defined in Data.YAML.Internal

Methods

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

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

Ord (Node loc) Source # 
Instance details

Defined in Data.YAML.Internal

Methods

compare :: Node loc -> Node loc -> Ordering #

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

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

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

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

max :: Node loc -> Node loc -> Node loc #

min :: Node loc -> Node loc -> Node loc #

Show loc => Show (Node loc) Source # 
Instance details

Defined in Data.YAML.Internal

Methods

showsPrec :: Int -> Node loc -> ShowS #

show :: Node loc -> String #

showList :: [Node loc] -> ShowS #

Generic (Node loc) Source # 
Instance details

Defined in Data.YAML.Internal

Associated Types

type Rep (Node loc) :: Type -> Type #

Methods

from :: Node loc -> Rep (Node loc) x #

to :: Rep (Node loc) x -> Node loc #

Loc loc => ToYAML (Node loc) Source # 
Instance details

Defined in Data.YAML

Methods

toYAML :: Node loc -> Node () Source #

loc ~ Pos => FromYAML (Node loc) Source #

Trivial instance

Instance details

Defined in Data.YAML

Methods

parseYAML :: Node Pos -> Parser (Node loc) Source #

type Rep (Node loc) Source # 
Instance details

Defined in Data.YAML.Internal

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.Internal

Methods

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

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

Ord Scalar Source # 
Instance details

Defined in Data.YAML.Schema.Internal

Show Scalar Source # 
Instance details

Defined in Data.YAML.Schema.Internal

Generic Scalar Source # 
Instance details

Defined in Data.YAML.Schema.Internal

Associated Types

type Rep Scalar :: Type -> Type #

Methods

from :: Scalar -> Rep Scalar x #

to :: Rep Scalar x -> Scalar #

NFData Scalar Source #

Since: 0.2.0

Instance details

Defined in Data.YAML.Schema.Internal

Methods

rnf :: Scalar -> () #

ToYAML Scalar Source #

Since: 0.2.1

Instance details

Defined in Data.YAML

Methods

toYAML :: Scalar -> Node () Source #

FromYAML Scalar Source #

Since: 0.2.1

Instance details

Defined in Data.YAML

type Rep Scalar Source # 
Instance details

Defined in Data.YAML.Schema.Internal

Source locations

data Pos Source #

Position in parsed YAML source

See also prettyPosWithSource.

NOTE: if posCharOffset is negative the Pos value doesn't refer to a proper location; this may be emitted in corner cases when no proper location can be inferred.

Constructors

Pos 

Fields

Instances
Eq Pos Source # 
Instance details

Defined in Data.YAML.Pos

Methods

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

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

Show Pos Source # 
Instance details

Defined in Data.YAML.Pos

Methods

showsPrec :: Int -> Pos -> ShowS #

show :: Pos -> String #

showList :: [Pos] -> ShowS #

Generic Pos Source # 
Instance details

Defined in Data.YAML.Pos

Associated Types

type Rep Pos :: Type -> Type #

Methods

from :: Pos -> Rep Pos x #

to :: Rep Pos x -> Pos #

NFData Pos Source #

Since: 0.2.0

Instance details

Defined in Data.YAML.Pos

Methods

rnf :: Pos -> () #

type Rep Pos Source # 
Instance details

Defined in Data.YAML.Pos

type Rep Pos = D1 (MetaData "Pos" "Data.YAML.Pos" "HsYAML-0.2.1.0-3n04Fs6nDN3CMPVb0vyYIF" False) (C1 (MetaCons "Pos" PrefixI True) ((S1 (MetaSel (Just "posByteOffset") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "posCharOffset") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) :*: (S1 (MetaSel (Just "posLine") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "posColumn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int))))

prettyPosWithSource :: Pos -> ByteString -> String -> String Source #

Pretty prints a Pos together with the line the Pos refers and the column position.

The input ByteString must be the same that was passed to the YAML decoding function that produced the Pos value. The String argument is inserted right after the line:column: in the first line. The pretty-printed position result String will be terminated by a trailing newline.

For instance,

prettyPosWithSource somePos someInput " error" ++ "unexpected character\n"

results in

11:7: error
    |
 11 | foo: | bar
    |        ^
unexpected character

Since: 0.2.1

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

YAML 1.2 Schema encoders

data SchemaEncoder Source #

Since: 0.2.0

failsafeSchemaEncoder :: SchemaEncoder Source #

"Failsafe" schema encoder as specified in YAML 1.2 / 10.1.2. Tag Resolution

Since: 0.2.0

jsonSchemaEncoder :: SchemaEncoder Source #

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

Since: 0.2.0

coreSchemaEncoder :: SchemaEncoder Source #

Core schema encoder as specified in YAML 1.2 / 10.3.2. Tag Resolution

Since: 0.2.0

Generalised AST construction

decodeLoader :: forall n m. MonadFix m => Loader m n -> ByteString -> m (Either (Pos, 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.

Since: 0.2.0

data Loader m n Source #

Structure defining how to construct a document tree/graph

Since: 0.2.0

Constructors

Loader 

Fields

type LoaderT m n = Pos -> m (Either (Pos, String) n) Source #

Helper type for Loader

Since: 0.2.0

type NodeId = Word Source #

Unique identifier for identifying nodes

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