yaml-0.8.11: Support for parsing and rendering YAML documents.

Safe HaskellNone
LanguageHaskell98

Data.Yaml

Contents

Description

Provides a high-level interface for processing YAML files.

This module reuses most of the infrastructure from the aeson package. This means that you can use all of the existing tools for JSON processing for processing YAML files. As a result, much of the documentation below mentions JSON; do not let that confuse you, it's intentional.

For the most part, YAML content translates directly into JSON, and therefore there is very little data loss. If you need to deal with YAML more directly (e.g., directly deal with aliases), you should use the Text.Libyaml module instead.

For documentation on the aeson types, functions, classes, and operators, please see the Data.Aeson module of the aeson package.

Synopsis

Types

data Value :: *

Constructors

Object !Object 
Array !Array 
String !Text 
Number !Scientific 
Bool !Bool 
Null 

type Object = HashMap Text Value

type Array = Vector Value

prettyPrintParseException :: ParseException -> String Source

Alternative to show to display a ParseException on the screen. Instead of displaying the data constructors applied to their arguments, a more textual output is returned. For example, instead of printing:

AesonException "The key \"foo\" was not found"

It looks more pleasant to print:

Aeson exception: The key "foo" was not found

Since 0.8.11

data YamlException Source

Constructors

YamlException String 
YamlParseException

problem, context, index, position line, position column

data YamlMark Source

The pointer position

Constructors

YamlMark 

Fields

yamlIndex :: Int
 
yamlLine :: Int
 
yamlColumn :: Int
 

Instances

Constructors and accessors

object :: [Pair] -> Value

(.=) :: ToJSON a => Text -> a -> Pair

(.:) :: FromJSON a => Object -> Text -> Parser a

(.:?) :: FromJSON a => Object -> Text -> Parser (Maybe a)

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

Parsing

parseMonad :: Monad m => (a -> Parser b) -> a -> m b Source

parseEither :: (a -> Parser b) -> a -> Either String b

parseMaybe :: (a -> Parser b) -> a -> Maybe b

Classes

class ToJSON a where

Minimal complete definition

Nothing

Methods

toJSON :: a -> Value

Instances

ToJSON Bool 
ToJSON Char 
ToJSON Double 
ToJSON Float 
ToJSON Int 
ToJSON Int8 
ToJSON Int16 
ToJSON Int32 
ToJSON Int64 
ToJSON Integer 
ToJSON Word 
ToJSON Word8 
ToJSON Word16 
ToJSON Word32 
ToJSON Word64 
ToJSON () 
ToJSON IntSet 
ToJSON ZonedTime 
ToJSON UTCTime 
ToJSON Text 
ToJSON Text 
ToJSON Value 
ToJSON DotNetTime 
ToJSON Scientific 
ToJSON Number 
ToJSON [Char] 
ToJSON a => ToJSON [a] 
ToJSON (Ratio Integer) 
HasResolution a => ToJSON (Fixed a) 
ToJSON a => ToJSON (Dual a) 
ToJSON a => ToJSON (First a) 
ToJSON a => ToJSON (Last a) 
ToJSON a => ToJSON (Maybe a) 
ToJSON a => ToJSON (IntMap a) 
ToJSON a => ToJSON (Set a) 
ToJSON v => ToJSON (Tree v) 
ToJSON a => ToJSON (Vector a) 
(Storable a, ToJSON a) => ToJSON (Vector a) 
(Prim a, ToJSON a) => ToJSON (Vector a) 
(Vector Vector a, ToJSON a) => ToJSON (Vector a) 
ToJSON a => ToJSON (HashSet a) 
(ToJSON a, ToJSON b) => ToJSON (Either a b) 
(ToJSON a, ToJSON b) => ToJSON (a, b) 
ToJSON v => ToJSON (Map String v) 
ToJSON v => ToJSON (Map Text v) 
ToJSON v => ToJSON (Map Text v) 
ToJSON v => ToJSON (HashMap String v) 
ToJSON v => ToJSON (HashMap Text v) 
ToJSON v => ToJSON (HashMap Text v) 
(ToJSON a, ToJSON b, ToJSON c) => ToJSON (a, b, c) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d) => ToJSON (a, b, c, d) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e) => ToJSON (a, b, c, d, e) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f) => ToJSON (a, b, c, d, e, f) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g) => ToJSON (a, b, c, d, e, f, g) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h) => ToJSON (a, b, c, d, e, f, g, h) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i) => ToJSON (a, b, c, d, e, f, g, h, i) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j) => ToJSON (a, b, c, d, e, f, g, h, i, j) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k) => ToJSON (a, b, c, d, e, f, g, h, i, j, k) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m, ToJSON n) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m, ToJSON n, ToJSON o) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 

class FromJSON a where

Minimal complete definition

Nothing

Methods

parseJSON :: Value -> Parser a

Instances

FromJSON Bool 
FromJSON Char 
FromJSON Double 
FromJSON Float 
FromJSON Int 
FromJSON Int8 
FromJSON Int16 
FromJSON Int32 
FromJSON Int64 
FromJSON Integer 
FromJSON Word 
FromJSON Word8 
FromJSON Word16 
FromJSON Word32 
FromJSON Word64 
FromJSON () 
FromJSON IntSet 
FromJSON ZonedTime 
FromJSON UTCTime 
FromJSON Text 
FromJSON Text 
FromJSON Value 
FromJSON DotNetTime 
FromJSON Scientific 
FromJSON Number 
FromJSON [Char] 
FromJSON a => FromJSON [a] 
FromJSON (Ratio Integer) 
HasResolution a => FromJSON (Fixed a) 
FromJSON a => FromJSON (Dual a) 
FromJSON a => FromJSON (First a) 
FromJSON a => FromJSON (Last a) 
FromJSON a => FromJSON (Maybe a) 
FromJSON a => FromJSON (IntMap a) 
(Ord a, FromJSON a) => FromJSON (Set a) 
FromJSON v => FromJSON (Tree v) 
FromJSON a => FromJSON (Vector a) 
(Storable a, FromJSON a) => FromJSON (Vector a) 
(Prim a, FromJSON a) => FromJSON (Vector a) 
(Vector Vector a, FromJSON a) => FromJSON (Vector a) 
(Eq a, Hashable a, FromJSON a) => FromJSON (HashSet a) 
(FromJSON a, FromJSON b) => FromJSON (Either a b) 
(FromJSON a, FromJSON b) => FromJSON (a, b) 
FromJSON v => FromJSON (Map String v) 
FromJSON v => FromJSON (Map Text v) 
FromJSON v => FromJSON (Map Text v) 
FromJSON v => FromJSON (HashMap String v) 
FromJSON v => FromJSON (HashMap Text v) 
FromJSON v => FromJSON (HashMap Text v) 
(FromJSON a, FromJSON b, FromJSON c) => FromJSON (a, b, c) 
(FromJSON a, FromJSON b, FromJSON c, FromJSON d) => FromJSON (a, b, c, d) 
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e) => FromJSON (a, b, c, d, e) 
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f) => FromJSON (a, b, c, d, e, f) 
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g) => FromJSON (a, b, c, d, e, f, g) 
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h) => FromJSON (a, b, c, d, e, f, g, h) 
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i) => FromJSON (a, b, c, d, e, f, g, h, i) 
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j) => FromJSON (a, b, c, d, e, f, g, h, i, j) 
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k) => FromJSON (a, b, c, d, e, f, g, h, i, j, k) 
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l) 
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m) 
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m, FromJSON n) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m, FromJSON n, FromJSON o) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 

Encoding/decoding

encodeFile :: ToJSON a => FilePath -> a -> IO () Source

Better error information

decodeEither' :: FromJSON a => ByteString -> Either ParseException a Source

More helpful version of decodeEither which returns the YamlException.

Since 0.8.3

decodeFileEither :: FromJSON a => FilePath -> IO (Either ParseException a) Source

A version of decodeFile which should not throw runtime exceptions.

Since 0.8.4

More control over decoding