| Copyright | © Herbert Valerio Riedel 2015-2018 | 
|---|---|
| License | GPL-2.0-or-later | 
| Safe Haskell | Safe | 
| Language | Haskell2010 | 
Data.YAML
Synopsis
- decode :: FromYAML v => ByteString -> Either (Pos, String) [v]
- decode1 :: FromYAML v => ByteString -> Either (Pos, String) v
- decodeStrict :: FromYAML v => ByteString -> Either (Pos, String) [v]
- decode1Strict :: FromYAML v => ByteString -> Either (Pos, String) v
- class FromYAML a where
- data Parser a
- parseEither :: Parser a -> Either (Pos, String) a
- failAtNode :: Node Pos -> String -> Parser a
- typeMismatch :: String -> Node Pos -> Parser a
- type Mapping loc = Map (Node loc) (Node loc)
- (.:) :: FromYAML a => Mapping Pos -> Text -> Parser a
- (.:?) :: FromYAML a => Mapping Pos -> Text -> Parser (Maybe a)
- (.:!) :: FromYAML a => Mapping Pos -> Text -> Parser (Maybe a)
- (.!=) :: Parser (Maybe a) -> a -> Parser a
- encode :: ToYAML v => [v] -> ByteString
- encode1 :: ToYAML v => v -> ByteString
- encodeStrict :: ToYAML v => [v] -> ByteString
- encode1Strict :: ToYAML v => v -> ByteString
- class ToYAML a where
- type Pair = (Node (), Node ())
- mapping :: [Pair] -> Node ()
- (.=) :: ToYAML a => Text -> a -> Pair
- withScalar :: String -> (Scalar -> Parser a) -> Node Pos -> Parser a
- withSeq :: String -> ([Node Pos] -> Parser a) -> Node Pos -> Parser a
- withBool :: String -> (Bool -> Parser a) -> Node Pos -> Parser a
- withFloat :: String -> (Double -> Parser a) -> Node Pos -> Parser a
- withInt :: String -> (Integer -> Parser a) -> Node Pos -> Parser a
- withNull :: String -> Parser a -> Node Pos -> Parser a
- withStr :: String -> (Text -> Parser a) -> Node Pos -> Parser a
- withMap :: String -> (Mapping Pos -> Parser a) -> Node Pos -> Parser a
- decodeNode :: ByteString -> Either (Pos, String) [Doc (Node Pos)]
- decodeNode' :: SchemaResolver -> Bool -> Bool -> ByteString -> Either (Pos, String) [Doc (Node Pos)]
- encodeNode :: [Doc (Node ())] -> ByteString
- encodeNode' :: SchemaEncoder -> Encoding -> [Doc (Node ())] -> ByteString
- newtype Doc n = Doc {- docRoot :: n
 
- data Node loc
- data Scalar
- data Pos = Pos {- posByteOffset :: !Int
- posCharOffset :: !Int
- posLine :: !Int
- posColumn :: !Int
 
- prettyPosWithSource :: Pos -> ByteString -> String -> String
- data SchemaResolver
- failsafeSchemaResolver :: SchemaResolver
- jsonSchemaResolver :: SchemaResolver
- coreSchemaResolver :: SchemaResolver
- data SchemaEncoder
- failsafeSchemaEncoder :: SchemaEncoder
- jsonSchemaEncoder :: SchemaEncoder
- coreSchemaEncoder :: SchemaEncoder
- decodeLoader :: forall n m. MonadFix m => Loader m n -> ByteString -> m (Either (Pos, String) [n])
- data Loader m n = Loader {}
- type LoaderT m n = Pos -> m (Either (Pos, String) n)
- type NodeId = Word
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" .!= FalseAnd 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 casedecode1raw of Left (loc,emsg) -> do hPutStrLn stderr (fname ++ ":" ++prettyPosWithSourceloc 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.
instanceToYAMLPerson where -- this generates aNodetoYAML(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) TextRight "Bar"
>>>decode1 "Foo\n---\nBar" :: Either (Pos,String) TextLeft (Pos {posByteOffset = 8, posCharOffset = 8, posLine = 3, posColumn = 0},"unexpected multiple YAML documents")
>>>decode1 "# Just a comment" :: Either (Pos,String) TextLeft (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
Instances
YAML Parser Monad used by FromYAML
See also parseEither or decode
Instances
| MonadFail Parser Source # | NOTE:  Since: 0.1.1.0 | 
| Alternative Parser Source # | Since: 0.1.1.0 | 
| Applicative Parser Source # | |
| Functor Parser Source # | |
| Monad Parser Source # | |
| MonadPlus Parser Source # | Since: 0.1.1.0 | 
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
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 Mappings
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
A type from which YAML nodes can be constructed
Since: 0.2.0.0
Instances
Accessors for encoding Mappings
Prism-style parsers
withScalar :: String -> (Scalar -> Parser a) -> Node Pos -> Parser a Source #
Operate on Scalar 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 Anchornodes
- Disallow cyclic anchor references
Since: 0.2.0
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
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
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
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
Source locations
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
| Generic Pos Source # | |
| Show Pos Source # | |
| NFData Pos Source # | Since: 0.2.0 | 
| Defined in Data.YAML.Pos | |
| Eq Pos Source # | |
| type Rep Pos Source # | |
| Defined in Data.YAML.Pos type Rep Pos = D1 ('MetaData "Pos" "Data.YAML.Pos" "HsYAML-0.2.1.3-Hr7MYud8xmoFaKjE4t08C4" '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 characterSince: 0.2.1
YAML 1.2 Schema resolvers
See also Data.YAML.Schema
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.
failsafeSchemaResolver :: SchemaResolver Source #
"Failsafe" schema resolver as specified in YAML 1.2 / 10.1.2. Tag Resolution
jsonSchemaResolver :: SchemaResolver Source #
Strict JSON schema resolver as specified in YAML 1.2 / 10.2.2. Tag Resolution
coreSchemaResolver :: SchemaResolver Source #
Core schema resolver as specified in YAML 1.2 / 10.3.2. Tag Resolution
YAML 1.2 Schema encoders
See also Data.YAML.Schema
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
Structure defining how to construct a document tree/graph
Since: 0.2.0