Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Low-level, streaming YAML interface. For a higher-level interface, see Data.Yaml.
Synopsis
- data MarkedEvent = MarkedEvent {}
- data Event
- data Style
- = Any
- | Plain
- | SingleQuoted
- | DoubleQuoted
- | Literal
- | Folded
- | PlainNoTag
- data SequenceStyle
- data MappingStyle
- data Tag
- type AnchorName = String
- type Anchor = Maybe AnchorName
- encode :: (MonadCatch m, MonadAsync m, MonadMask m) => SerialT m Event -> m ByteString
- encodeWith :: (MonadCatch m, MonadAsync m, MonadMask m) => FormatOptions -> SerialT m Event -> m ByteString
- decode :: (MonadCatch m, MonadAsync m, MonadMask m) => ByteString -> SerialT m Event
- decodeMarked :: (MonadCatch m, MonadAsync m, MonadMask m) => ByteString -> SerialT m MarkedEvent
- encodeFile :: (MonadCatch m, MonadAsync m, MonadMask m) => FilePath -> SerialT m Event -> m ()
- decodeFile :: (MonadCatch m, MonadAsync m, MonadMask m) => FilePath -> SerialT m Event
- decodeFileMarked :: (MonadCatch m, MonadAsync m, MonadMask m) => FilePath -> SerialT m MarkedEvent
- encodeFileWith :: (MonadCatch m, MonadAsync m, MonadMask m) => FormatOptions -> FilePath -> SerialT m Event -> m ()
- data FormatOptions
- defaultFormatOptions :: FormatOptions
- setWidth :: Maybe Int -> FormatOptions -> FormatOptions
- setTagRendering :: (Event -> TagRender) -> FormatOptions -> FormatOptions
- renderScalarTags :: Event -> TagRender
- renderAllTags :: Event -> TagRender
- renderNoTags :: Event -> TagRender
- renderUriTags :: Event -> TagRender
- data YamlException
- data YamlMark = YamlMark {}
The event stream
data MarkedEvent Source #
Event with start and end marks.
Since: 0.10.4.0
Instances
Style for scalars - e.g. quoted / folded
Instances
Data Style Source # | |
Defined in Text.Libyaml 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 # 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 # | |
Enum Style Source # | |
Generic Style Source # | |
Read Style Source # | |
Show Style Source # | |
NFData Style Source # | |
Defined in Text.Libyaml | |
Eq Style Source # | |
Ord Style Source # | |
type Rep Style Source # | |
Defined in Text.Libyaml type Rep Style = D1 ('MetaData "Style" "Text.Libyaml" "libyaml-streamly-0.2.2-D6FPLObSZacDNsBukFH5SK" '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
data MappingStyle Source #
Style for mappings - e.g. block or flow
Since: 0.9.0
Instances
Instances
Data Tag Source # | |
Defined in Text.Libyaml 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 # 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 # | |
Read Tag Source # | |
Show Tag Source # | |
NFData Tag Source # | |
Defined in Text.Libyaml | |
Eq Tag Source # | |
type Rep Tag Source # | |
Defined in Text.Libyaml type Rep Tag = D1 ('MetaData "Tag" "Text.Libyaml" "libyaml-streamly-0.2.2-D6FPLObSZacDNsBukFH5SK" '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))))) |
type AnchorName = String Source #
type Anchor = Maybe AnchorName Source #
Encoding and decoding
encode :: (MonadCatch m, MonadAsync m, MonadMask m) => SerialT m Event -> m ByteString Source #
encodeWith :: (MonadCatch m, MonadAsync m, MonadMask m) => FormatOptions -> SerialT m Event -> m ByteString Source #
decode :: (MonadCatch m, MonadAsync m, MonadMask m) => ByteString -> SerialT m Event Source #
decodeMarked :: (MonadCatch m, MonadAsync m, MonadMask m) => ByteString -> SerialT m MarkedEvent Source #
encodeFile :: (MonadCatch m, MonadAsync m, MonadMask m) => FilePath -> SerialT m Event -> m () Source #
decodeFile :: (MonadCatch m, MonadAsync m, MonadMask m) => FilePath -> SerialT m Event Source #
decodeFileMarked :: (MonadCatch m, MonadAsync m, MonadMask m) => FilePath -> SerialT m MarkedEvent Source #
encodeFileWith :: (MonadCatch m, MonadAsync m, MonadMask m) => FormatOptions -> FilePath -> SerialT m Event -> m () Source #
data FormatOptions Source #
Contains options relating to the formatting (indendation, width) of the YAML output.
Since: 0.10.2.0
defaultFormatOptions :: FormatOptions Source #
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 #
YamlException String | |
YamlParseException | problem, context, index, position line, position column |
Instances
The pointer position
Instances
Generic YamlMark Source # | |
Show YamlMark Source # | |
NFData YamlMark Source # | |
Defined in Text.Libyaml | |
type Rep YamlMark Source # | |
Defined in Text.Libyaml type Rep YamlMark = D1 ('MetaData "YamlMark" "Text.Libyaml" "libyaml-streamly-0.2.2-D6FPLObSZacDNsBukFH5SK" '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)))) |