libyaml-streamly-0.2.3.0: Low-level, streaming YAML interface via streamly.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.Libyaml

Description

Low-level, streaming YAML interface. For a higher-level interface, see Data.Yaml.

Synopsis

The event stream

data MarkedEvent Source #

Event with start and end marks.

Since: 0.10.4.0

data Event Source #

Instances

Instances details
Generic Event Source # 
Instance details

Defined in Text.Libyaml

Associated Types

type Rep Event :: Type -> Type #

Methods

from :: Event -> Rep Event x #

to :: Rep Event x -> Event #

Show Event Source # 
Instance details

Defined in Text.Libyaml

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

NFData Event Source # 
Instance details

Defined in Text.Libyaml

Methods

rnf :: Event -> () #

Eq Event Source # 
Instance details

Defined in Text.Libyaml

Methods

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

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

type Rep Event Source # 
Instance details

Defined in Text.Libyaml

type Rep Event = D1 ('MetaData "Event" "Text.Libyaml" "libyaml-streamly-0.2.3.0-6iTjypt1xIFJSQ9xQQ49kN" 'False) (((C1 ('MetaCons "EventStreamStart" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EventStreamEnd" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EventDocumentStart" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EventDocumentEnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EventAlias" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 AnchorName))))) :+: ((C1 ('MetaCons "EventScalar" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Tag)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Style) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Anchor))) :+: C1 ('MetaCons "EventSequenceStart" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Tag) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SequenceStyle) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Anchor)))) :+: (C1 ('MetaCons "EventSequenceEnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EventMappingStart" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Tag) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MappingStyle) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Anchor))) :+: C1 ('MetaCons "EventMappingEnd" 'PrefixI 'False) (U1 :: Type -> Type)))))

data Style Source #

Style for scalars - e.g. quoted / folded

Instances

Instances details
Data Style Source # 
Instance details

Defined in Text.Libyaml

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Style -> c Style #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Style #

toConstr :: Style -> Constr #

dataTypeOf :: Style -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Style) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Style) #

gmapT :: (forall b. Data b => b -> b) -> Style -> Style #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r #

gmapQ :: (forall d. Data d => d -> u) -> Style -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Style -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Style -> m Style #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Style -> m Style #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Style -> m Style #

Bounded Style Source # 
Instance details

Defined in Text.Libyaml

Enum Style Source # 
Instance details

Defined in Text.Libyaml

Generic Style Source # 
Instance details

Defined in Text.Libyaml

Associated Types

type Rep Style :: Type -> Type #

Methods

from :: Style -> Rep Style x #

to :: Rep Style x -> Style #

Read Style Source # 
Instance details

Defined in Text.Libyaml

Show Style Source # 
Instance details

Defined in Text.Libyaml

Methods

showsPrec :: Int -> Style -> ShowS #

show :: Style -> String #

showList :: [Style] -> ShowS #

NFData Style Source # 
Instance details

Defined in Text.Libyaml

Methods

rnf :: Style -> () #

Eq Style Source # 
Instance details

Defined in Text.Libyaml

Methods

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

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

Ord Style Source # 
Instance details

Defined in Text.Libyaml

Methods

compare :: Style -> Style -> Ordering #

(<) :: Style -> Style -> Bool #

(<=) :: Style -> Style -> Bool #

(>) :: Style -> Style -> Bool #

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

max :: Style -> Style -> Style #

min :: Style -> Style -> Style #

type Rep Style Source # 
Instance details

Defined in Text.Libyaml

type Rep Style = D1 ('MetaData "Style" "Text.Libyaml" "libyaml-streamly-0.2.3.0-6iTjypt1xIFJSQ9xQQ49kN" 'False) ((C1 ('MetaCons "Any" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Plain" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SingleQuoted" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "DoubleQuoted" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Literal" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Folded" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PlainNoTag" 'PrefixI 'False) (U1 :: Type -> Type))))

data SequenceStyle Source #

Style for sequences - e.g. block or flow

Since: 0.9.0

Instances

Instances details
Data SequenceStyle Source # 
Instance details

Defined in Text.Libyaml

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SequenceStyle -> c SequenceStyle #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SequenceStyle #

toConstr :: SequenceStyle -> Constr #

dataTypeOf :: SequenceStyle -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SequenceStyle) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SequenceStyle) #

gmapT :: (forall b. Data b => b -> b) -> SequenceStyle -> SequenceStyle #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SequenceStyle -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SequenceStyle -> r #

gmapQ :: (forall d. Data d => d -> u) -> SequenceStyle -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SequenceStyle -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SequenceStyle -> m SequenceStyle #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SequenceStyle -> m SequenceStyle #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SequenceStyle -> m SequenceStyle #

Bounded SequenceStyle Source # 
Instance details

Defined in Text.Libyaml

Enum SequenceStyle Source # 
Instance details

Defined in Text.Libyaml

Generic SequenceStyle Source # 
Instance details

Defined in Text.Libyaml

Associated Types

type Rep SequenceStyle :: Type -> Type #

Show SequenceStyle Source # 
Instance details

Defined in Text.Libyaml

NFData SequenceStyle Source # 
Instance details

Defined in Text.Libyaml

Methods

rnf :: SequenceStyle -> () #

Eq SequenceStyle Source # 
Instance details

Defined in Text.Libyaml

Ord SequenceStyle Source # 
Instance details

Defined in Text.Libyaml

type Rep SequenceStyle Source # 
Instance details

Defined in Text.Libyaml

type Rep SequenceStyle = D1 ('MetaData "SequenceStyle" "Text.Libyaml" "libyaml-streamly-0.2.3.0-6iTjypt1xIFJSQ9xQQ49kN" 'False) (C1 ('MetaCons "AnySequence" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BlockSequence" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FlowSequence" 'PrefixI 'False) (U1 :: Type -> Type)))

data MappingStyle Source #

Style for mappings - e.g. block or flow

Since: 0.9.0

Instances

Instances details
Data MappingStyle Source # 
Instance details

Defined in Text.Libyaml

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MappingStyle -> c MappingStyle #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MappingStyle #

toConstr :: MappingStyle -> Constr #

dataTypeOf :: MappingStyle -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MappingStyle) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MappingStyle) #

gmapT :: (forall b. Data b => b -> b) -> MappingStyle -> MappingStyle #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MappingStyle -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MappingStyle -> r #

gmapQ :: (forall d. Data d => d -> u) -> MappingStyle -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MappingStyle -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MappingStyle -> m MappingStyle #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MappingStyle -> m MappingStyle #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MappingStyle -> m MappingStyle #

Bounded MappingStyle Source # 
Instance details

Defined in Text.Libyaml

Enum MappingStyle Source # 
Instance details

Defined in Text.Libyaml

Generic MappingStyle Source # 
Instance details

Defined in Text.Libyaml

Associated Types

type Rep MappingStyle :: Type -> Type #

Show MappingStyle Source # 
Instance details

Defined in Text.Libyaml

NFData MappingStyle Source # 
Instance details

Defined in Text.Libyaml

Methods

rnf :: MappingStyle -> () #

Eq MappingStyle Source # 
Instance details

Defined in Text.Libyaml

Ord MappingStyle Source # 
Instance details

Defined in Text.Libyaml

type Rep MappingStyle Source # 
Instance details

Defined in Text.Libyaml

type Rep MappingStyle = D1 ('MetaData "MappingStyle" "Text.Libyaml" "libyaml-streamly-0.2.3.0-6iTjypt1xIFJSQ9xQQ49kN" 'False) (C1 ('MetaCons "AnyMapping" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BlockMapping" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FlowMapping" 'PrefixI 'False) (U1 :: Type -> Type)))

data Tag Source #

Instances

Instances details
Data Tag Source # 
Instance details

Defined in Text.Libyaml

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tag -> c Tag #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Tag #

toConstr :: Tag -> Constr #

dataTypeOf :: Tag -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Tag) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tag) #

gmapT :: (forall b. Data b => b -> b) -> Tag -> Tag #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r #

gmapQ :: (forall d. Data d => d -> u) -> Tag -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Tag -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tag -> m Tag #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tag -> m Tag #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tag -> m Tag #

Generic Tag Source # 
Instance details

Defined in Text.Libyaml

Associated Types

type Rep Tag :: Type -> Type #

Methods

from :: Tag -> Rep Tag x #

to :: Rep Tag x -> Tag #

Read Tag Source # 
Instance details

Defined in Text.Libyaml

Show Tag Source # 
Instance details

Defined in Text.Libyaml

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

NFData Tag Source # 
Instance details

Defined in Text.Libyaml

Methods

rnf :: Tag -> () #

Eq Tag Source # 
Instance details

Defined in Text.Libyaml

Methods

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

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

type Rep Tag Source # 
Instance details

Defined in Text.Libyaml

type Rep Tag = D1 ('MetaData "Tag" "Text.Libyaml" "libyaml-streamly-0.2.3.0-6iTjypt1xIFJSQ9xQQ49kN" 'False) (((C1 ('MetaCons "StrTag" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FloatTag" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NullTag" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BoolTag" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SetTag" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "IntTag" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SeqTag" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MapTag" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "UriTag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 String)) :+: C1 ('MetaCons "NoTag" 'PrefixI 'False) (U1 :: Type -> Type)))))

Encoding and decoding

data FormatOptions Source #

Contains options relating to the formatting (indendation, width) of the YAML output.

Since: 0.10.2.0

setWidth :: Maybe Int -> FormatOptions -> FormatOptions Source #

Set the maximum number of columns in the YAML output, or Nothing for infinite. By default, the limit is 80 characters.

Since: 0.10.2.0

setTagRendering :: (Event -> TagRender) -> FormatOptions -> FormatOptions Source #

Control when and whether tags are rendered to output.

Since: 0.1.1.0

renderScalarTags :: Event -> TagRender Source #

A value for formatOptionsRenderTags that renders no collection tags but all scalar tags (unless suppressed with styles 'NoTag or PlainNoTag).

Since: 0.1.1.0

renderAllTags :: Event -> TagRender Source #

A value for formatOptionsRenderTags that renders all tags (except NoTag tag and PlainNoTag style).

Since: 0.1.1.0

renderNoTags :: Event -> TagRender Source #

A value for formatOptionsRenderTags that renders no tags.

Since: 0.1.1.0

renderUriTags :: Event -> TagRender Source #

A value for formatOptionsRenderCollectionTags that renders tags which are instances of UriTag

Since: 0.1.1.0

Error handling

data YamlException Source #

Constructors

YamlException String 
YamlParseException

problem, context, index, position line, position column

Instances

Instances details
Exception YamlException Source # 
Instance details

Defined in Text.Libyaml

Generic YamlException Source # 
Instance details

Defined in Text.Libyaml

Associated Types

type Rep YamlException :: Type -> Type #

Show YamlException Source # 
Instance details

Defined in Text.Libyaml

NFData YamlException Source # 
Instance details

Defined in Text.Libyaml

Methods

rnf :: YamlException -> () #

type Rep YamlException Source # 
Instance details

Defined in Text.Libyaml

type Rep YamlException = D1 ('MetaData "YamlException" "Text.Libyaml" "libyaml-streamly-0.2.3.0-6iTjypt1xIFJSQ9xQQ49kN" 'False) (C1 ('MetaCons "YamlException" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 String)) :+: C1 ('MetaCons "YamlParseException" 'PrefixI 'True) (S1 ('MetaSel ('Just "yamlProblem") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 String) :*: (S1 ('MetaSel ('Just "yamlContext") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 String) :*: S1 ('MetaSel ('Just "yamlProblemMark") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 YamlMark))))

data YamlMark Source #

The pointer position

Constructors

YamlMark 

Fields

Instances

Instances details
Generic YamlMark Source # 
Instance details

Defined in Text.Libyaml

Associated Types

type Rep YamlMark :: Type -> Type #

Methods

from :: YamlMark -> Rep YamlMark x #

to :: Rep YamlMark x -> YamlMark #

Show YamlMark Source # 
Instance details

Defined in Text.Libyaml

NFData YamlMark Source # 
Instance details

Defined in Text.Libyaml

Methods

rnf :: YamlMark -> () #

type Rep YamlMark Source # 
Instance details

Defined in Text.Libyaml

type Rep YamlMark = D1 ('MetaData "YamlMark" "Text.Libyaml" "libyaml-streamly-0.2.3.0-6iTjypt1xIFJSQ9xQQ49kN" 'False) (C1 ('MetaCons "YamlMark" 'PrefixI 'True) (S1 ('MetaSel ('Just "yamlIndex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Just "yamlLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "yamlColumn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int))))