HsYAML-0.2.0.0: Pure Haskell YAML 1.2 processor
Copyright© Oren Ben-Kiki 2007
© Herbert Valerio Riedel 2015-2018
LicenseGPL-2.0-or-later
Safe HaskellSafe
LanguageHaskell2010

Data.YAML.Token

Description

Tokenizer for the YAML 1.2 syntax as defined in http://yaml.org/spec/1.2/spec.html.

Synopsis

Documentation

tokenize :: ByteString -> Bool -> [Token] Source #

tokenize input emit_unparsed converts the Unicode input (using the UTF-8, UTF-16 (LE or BE), or UTF-32 (LE or BE) encoding) to a list of Token according to the YAML 1.2 specification.

Errors are reported as tokens with Error :: Code, and the unparsed text following an error may be attached as a final Unparsed token (if the emit_unparsed argument is True). Note that tokens are available "immediately", allowing for streaming of large YAML files with memory requirements depending only on the YAML nesting level.

data Token Source #

Parsed token.

Constructors

Token 

Fields

Instances

Instances details
Show Token Source # 
Instance details

Defined in Data.YAML.Token

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

Generic Token Source # 
Instance details

Defined in Data.YAML.Token

Associated Types

type Rep Token :: Type -> Type #

Methods

from :: Token -> Rep Token x #

to :: Rep Token x -> Token #

NFData Token Source #

Since: 0.2.0

Instance details

Defined in Data.YAML.Token

Methods

rnf :: Token -> () #

type Rep Token Source # 
Instance details

Defined in Data.YAML.Token

data Code Source #

Token codes.

Constructors

Bom

BOM, contains "TF8", "TF16LE", "TF32BE", etc.

Text

Content text characters.

Meta

Non-content (meta) text characters.

Break

Separation line break.

LineFeed

Line break normalized to content line feed.

LineFold

Line break folded to content space.

Indicator

Character indicating structure.

White

Separation white space.

Indent

Indentation spaces.

DirectivesEnd

Document start marker.

DocumentEnd

Document end marker.

BeginEscape

Begins escape sequence.

EndEscape

Ends escape sequence.

BeginComment

Begins comment.

EndComment

Ends comment.

BeginDirective

Begins directive.

EndDirective

Ends directive.

BeginTag

Begins tag.

EndTag

Ends tag.

BeginHandle

Begins tag handle.

EndHandle

Ends tag handle.

BeginAnchor

Begins anchor.

EndAnchor

Ends anchor.

BeginProperties

Begins node properties.

EndProperties

Ends node properties.

BeginAlias

Begins alias.

EndAlias

Ends alias.

BeginScalar

Begins scalar content.

EndScalar

Ends scalar content.

BeginSequence

Begins sequence content.

EndSequence

Ends sequence content.

BeginMapping

Begins mapping content.

EndMapping

Ends mapping content.

BeginPair

Begins mapping key:value pair.

EndPair

Ends mapping key:value pair.

BeginNode

Begins complete node.

EndNode

Ends complete node.

BeginDocument

Begins document.

EndDocument

Ends document.

BeginStream

Begins YAML stream.

EndStream

Ends YAML stream.

Error

Parsing error at this point.

Unparsed

Unparsed due to errors (or at end of test).

Detected

Detected parameter (for testing).

Instances

Instances details
Eq Code Source # 
Instance details

Defined in Data.YAML.Token

Methods

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

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

Show Code Source # 
Instance details

Defined in Data.YAML.Token

Methods

showsPrec :: Int -> Code -> ShowS #

show :: Code -> String #

showList :: [Code] -> ShowS #

Generic Code Source # 
Instance details

Defined in Data.YAML.Token

Associated Types

type Rep Code :: Type -> Type #

Methods

from :: Code -> Rep Code x #

to :: Rep Code x -> Code #

NFData Code Source #

Since: 0.2.0

Instance details

Defined in Data.YAML.Token

Methods

rnf :: Code -> () #

type Rep Code Source # 
Instance details

Defined in Data.YAML.Token

type Rep Code = D1 ('MetaData "Code" "Data.YAML.Token" "HsYAML-0.2.0.0-inplace" 'False) (((((C1 ('MetaCons "Bom" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Text" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Meta" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Break" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LineFeed" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "LineFold" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Indicator" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "White" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Indent" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DirectivesEnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DocumentEnd" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "BeginEscape" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EndEscape" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BeginComment" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EndComment" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BeginDirective" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "EndDirective" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BeginTag" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EndTag" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "BeginHandle" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EndHandle" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BeginAnchor" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "EndAnchor" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BeginProperties" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EndProperties" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BeginAlias" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EndAlias" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "BeginScalar" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EndScalar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BeginSequence" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "EndSequence" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BeginMapping" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EndMapping" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "BeginPair" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EndPair" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BeginNode" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EndNode" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BeginDocument" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "EndDocument" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BeginStream" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EndStream" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Error" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Unparsed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Detected" 'PrefixI 'False) (U1 :: Type -> Type)))))))

data Encoding Source #

Recognized Unicode encodings. As of YAML 1.2 UTF-32 is also required.

Constructors

UTF8

UTF-8 encoding (or ASCII)

UTF16LE

UTF-16 little endian

UTF16BE

UTF-16 big endian

UTF32LE

UTF-32 little endian

UTF32BE

UTF-32 big endian

Instances

Instances details
Eq Encoding Source # 
Instance details

Defined in Data.YAML.Token.Encoding

Show Encoding Source #

show encoding converts an Encoding to the encoding name (with a "-") as used by most programs.

Instance details

Defined in Data.YAML.Token.Encoding

Generic Encoding Source # 
Instance details

Defined in Data.YAML.Token.Encoding

Associated Types

type Rep Encoding :: Type -> Type #

Methods

from :: Encoding -> Rep Encoding x #

to :: Rep Encoding x -> Encoding #

NFData Encoding Source #

Since: 0.2.0

Instance details

Defined in Data.YAML.Token.Encoding

Methods

rnf :: Encoding -> () #

type Rep Encoding Source # 
Instance details

Defined in Data.YAML.Token.Encoding

type Rep Encoding = D1 ('MetaData "Encoding" "Data.YAML.Token.Encoding" "HsYAML-0.2.0.0-inplace" 'False) ((C1 ('MetaCons "UTF8" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UTF16LE" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UTF16BE" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "UTF32LE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UTF32BE" 'PrefixI 'False) (U1 :: Type -> Type))))