Copyright | © Herbert Valerio Riedel 2015-2018 |
---|---|
License | GPL-2.0-or-later |
Safe Haskell | Safe |
Language | Haskell2010 |
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
- decode :: FromYAML v => ByteString -> Either String [v]
- decodeStrict :: FromYAML v => ByteString -> Either String [v]
- class FromYAML a where
- data Parser a
- parseEither :: Parser a -> Either String a
- typeMismatch :: String -> Node -> Parser a
- type Mapping = Map Node Node
- (.:) :: FromYAML a => Mapping -> Text -> Parser a
- (.:?) :: FromYAML a => Mapping -> Text -> Parser (Maybe a)
- (.:!) :: FromYAML a => Mapping -> Text -> Parser (Maybe a)
- (.!=) :: Parser (Maybe a) -> a -> Parser a
- withSeq :: String -> ([Node] -> Parser a) -> Node -> Parser a
- withBool :: String -> (Bool -> Parser a) -> Node -> Parser a
- withFloat :: String -> (Double -> Parser a) -> Node -> Parser a
- withInt :: String -> (Integer -> Parser a) -> Node -> Parser a
- withNull :: String -> Parser a -> Node -> Parser a
- withStr :: String -> (Text -> Parser a) -> Node -> Parser a
- withMap :: String -> (Mapping -> Parser a) -> Node -> Parser a
- decodeNode :: ByteString -> Either String [Doc Node]
- decodeNode' :: SchemaResolver -> Bool -> Bool -> ByteString -> Either String [Doc Node]
- newtype Doc n = Doc n
- data Node
- data Scalar
- data SchemaResolver = SchemaResolver {}
- failsafeSchemaResolver :: SchemaResolver
- jsonSchemaResolver :: SchemaResolver
- coreSchemaResolver :: SchemaResolver
- decodeLoader :: forall n m. MonadFix m => Loader m n -> ByteString -> m (Either String [n])
- data Loader m n = Loader {}
- type NodeId = Word
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).
decodeStrict :: FromYAML v => ByteString -> Either String [v] Source #
Like decode
but takes a strict ByteString
Since: HsYAML-0.1.1.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
parseEither :: Parser a -> Either String a Source #
Run Parser
A common use-case is parseEither
parseYAML
.
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: HsYAML-0.1.1.0
Accessors for YAML Mapping
s
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
:: 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
YAML Document tree/graph
Doc n |
YAML Document node
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 |
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.
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 JSON schema resolver as specified in YAML 1.2 / 10.3.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.
Structure defining how to construct a document tree/graph