libyaml-0.1.0.0: Low-level, streaming YAML interface.

Safe HaskellNone
LanguageHaskell2010

Text.Libyaml

Contents

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: libyaml-0.10.4.0

data Style Source #

Style for scalars - e.g. quoted / folded

Instances
Bounded Style Source # 
Instance details

Defined in Text.Libyaml

Enum Style Source # 
Instance details

Defined in Text.Libyaml

Eq Style Source # 
Instance details

Defined in Text.Libyaml

Methods

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

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

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 :: (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 #

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 #

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 #

data SequenceStyle Source #

Style for sequences - e.g. block or flow

Since: libyaml-0.9.0

Instances
Bounded SequenceStyle Source # 
Instance details

Defined in Text.Libyaml

Enum SequenceStyle Source # 
Instance details

Defined in Text.Libyaml

Eq SequenceStyle Source # 
Instance details

Defined in Text.Libyaml

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 :: (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 #

Ord SequenceStyle Source # 
Instance details

Defined in Text.Libyaml

Show SequenceStyle Source # 
Instance details

Defined in Text.Libyaml

data MappingStyle Source #

Style for mappings - e.g. block or flow

Since: libyaml-0.9.0

Instances
Bounded MappingStyle Source # 
Instance details

Defined in Text.Libyaml

Enum MappingStyle Source # 
Instance details

Defined in Text.Libyaml

Eq MappingStyle Source # 
Instance details

Defined in Text.Libyaml

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 :: (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 #

Ord MappingStyle Source # 
Instance details

Defined in Text.Libyaml

Show MappingStyle Source # 
Instance details

Defined in Text.Libyaml

data Tag Source #

Instances
Eq Tag Source # 
Instance details

Defined in Text.Libyaml

Methods

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

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

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 :: (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 #

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 #

Encoding and decoding

encodeWith :: MonadResource m => FormatOptions -> ConduitM Event o m ByteString Source #

Since: libyaml-0.10.2.0

decode :: MonadResource m => ByteString -> ConduitM i Event m () Source #

Create a conduit that yields events from a bytestring.

decodeMarked :: MonadResource m => ByteString -> ConduitM i MarkedEvent m () Source #

Create a conduit that yields marked events from a bytestring.

This conduit will yield identical events to that of "decode", but also includes start and end marks for each event.

Since: libyaml-0.10.4.0

decodeFile :: MonadResource m => FilePath -> ConduitM i Event m () Source #

Creata a conduit that yields events from a file.

decodeFileMarked :: MonadResource m => FilePath -> ConduitM i MarkedEvent m () Source #

Create a conduit that yields marked events from a file.

This conduit will yield identical events to that of "decodeFile", but also includes start and end marks for each event.

Since: libyaml-0.10.4.0

encodeFileWith :: MonadResource m => FormatOptions -> FilePath -> ConduitM Event o m () Source #

Since: libyaml-0.10.2.0

data FormatOptions Source #

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

Since: libyaml-0.10.2.0

defaultFormatOptions :: FormatOptions Source #

Since: libyaml-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: libyaml-0.10.2.0

Error handling

data YamlMark Source #

The pointer position

Constructors

YamlMark 

Fields

Instances
Show YamlMark Source # 
Instance details

Defined in Text.Libyaml