Copyright | © Herbert Valerio Riedel 2015-2018 |
---|---|
License | GPL-2.0-or-later |
Safe Haskell | Safe |
Language | Haskell2010 |
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
- mapping :: [Pair] -> Node ()
- (.=) :: ToYAML a => Text -> a -> Pair
- 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 n
- data Node loc
- data Scalar
- data Pos = Pos {
- posByteOffset :: !Int
- posCharOffset :: !Int
- posLine :: !Int
- posColumn :: !Int
- 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" .!= 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.
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.
instanceToYAML
Person where -- this generates aNode
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
Instances
YAML Parser Monad
used by FromYAML
See also parseEither
or decode
Instances
Monad Parser Source # | |
Functor Parser Source # | |
MonadFail Parser Source # | NOTE: Since: 0.1.1.0 |
Applicative Parser Source # | |
Alternative Parser Source # | Since: 0.1.1.0 |
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 Mapping
s
Typeclass-based dumping
encode :: ToYAML v => [v] -> ByteString Source #
Serialize YAML Node(s) using the YAML 1.2 Core schema to a lazy 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
.
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
ToYAML Bool Source # | |
ToYAML Double Source # | |
ToYAML Int Source # | |
ToYAML Int8 Source # | |
ToYAML Int16 Source # | |
ToYAML Int32 Source # | |
ToYAML Int64 Source # | |
ToYAML Integer Source # | |
ToYAML Natural Source # | |
ToYAML Word Source # | |
ToYAML Word8 Source # | |
ToYAML Word16 Source # | |
ToYAML Word32 Source # | |
ToYAML Word64 Source # | |
ToYAML Text Source # | |
ToYAML a => ToYAML [a] Source # | |
ToYAML a => ToYAML (Maybe a) Source # | |
Loc loc => ToYAML (Node loc) Source # | |
(ToYAML a, ToYAML b) => ToYAML (a, b) Source # | |
(Ord k, ToYAML k, ToYAML v) => ToYAML (Map k v) Source # | |
(ToYAML a, ToYAML b, ToYAML c) => ToYAML (a, b, c) Source # | |
(ToYAML a, ToYAML b, ToYAML c, ToYAML d) => ToYAML (a, b, c, d) Source # | |
(ToYAML a, ToYAML b, ToYAML c, ToYAML d, ToYAML e) => ToYAML (a, b, c, d, e) Source # | |
(ToYAML a, ToYAML b, ToYAML c, ToYAML d, ToYAML e, ToYAML f) => ToYAML (a, b, c, d, e, f) Source # | |
(ToYAML a, ToYAML b, ToYAML c, ToYAML d, ToYAML e, ToYAML f, ToYAML g) => ToYAML (a, b, c, d, e, f, g) Source # | |
Accessors for encoding
Prism-style parsers
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
:: 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 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
Since: 0.2.0
YAML Document tree/graph
Doc n |
YAML Document node
Since: 0.2.0
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
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
Position in parsed YAML source
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.
Pos | |
|
Instances
Eq Pos Source # | |
Show Pos Source # | |
Generic Pos Source # | |
NFData Pos Source # | Since: 0.2.0 |
Defined in Data.YAML.Event.Internal | |
type Rep Pos Source # | |
Defined in Data.YAML.Event.Internal type Rep Pos = D1 ('MetaData "Pos" "Data.YAML.Event.Internal" "HsYAML-0.2.0.0-inplace" '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)))) |
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