Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data PackStreamError
- newtype PackStream a = PackStream {}
- class PackStreamValue a where
- pack :: a -> ByteString
- unpack :: PackStream a
- unpackStream :: PackStream a -> ByteString -> Either PackStreamError a
- unpackFail :: (MonadFail m, PackStreamValue a) => ByteString -> m a
- unpackThrow :: (MonadError PackStreamError m, PackStreamValue a) => ByteString -> m a
- data Value
- class ToValue a where
- class FromValue a where
- fromValue :: Value -> Either PackStreamError a
- (=:) :: ToValue a => Text -> a -> (Text, Value)
- at :: (MonadError PackStreamError m, FromValue a) => Map Text Value -> Text -> m a
- data Structure = Structure {}
Documentation
data PackStreamError Source #
Basic PackStream
error type that is used to handle parsing errors.
NotNull | This |
NotBool | This |
NotWord | This |
NotInt | This |
NotFloat | This |
NotString | This |
NotBytes | This |
NotList | This |
NotDict | This |
NotStructure | This |
NotValue | This |
WrongStructure Text | This |
DictHasNoKey Text | The dictionary doesn't have a specified |
Instances
newtype PackStream a Source #
Basic parser type. It works like parser combinators for binary data that represents PackStream.
Instances
class PackStreamValue a where Source #
The data types that can be interpreted or parsed to/from PackStream
ByteString
pack :: a -> ByteString Source #
Pack a value into a PackStream
ByteString
unpack :: PackStream a Source #
Parse a value from a PackStream
ByteString
Instances
unpackStream :: PackStream a -> ByteString -> Either PackStreamError a Source #
Use specific parser combinator to parse the ByteString
that represents any PackStream
data.
unpackFail :: (MonadFail m, PackStreamValue a) => ByteString -> m a Source #
Unpack some value of the specific type from ByteString
or fail
unpackThrow :: (MonadError PackStreamError m, PackStreamValue a) => ByteString -> m a Source #
Unpack some value of the specific type from ByteString
or raise PackStreamError
PackStream offers a number of core data types, many supported by multiple binary representations, as well as a flexible extension mechanism.
N | Missing or empty value |
B Bool | True or False |
I Int | Signed 64-bit integer |
F Double | 64-bit floating point number |
U ByteString | Byte array |
T Text | Unicode text, UTF-8 |
L [Value] | Ordered collection of |
D (Map Text Value) | Collection of key-value entries (no order guaranteed) |
S Structure | Composite value with a type signature |
class ToValue a where Source #
The data types that can be serialized as PackStream
Instances
ToValue Bool Source # | |
ToValue Double Source # | |
ToValue Int Source # | |
ToValue Integer Source # | |
ToValue () Source # | |
Defined in Data.PackStream.Internal.Type | |
ToValue ByteString Source # | |
Defined in Data.PackStream.Internal.Type toValue :: ByteString -> Value Source # | |
ToValue Text Source # | |
ToValue Structure Source # | |
ToValue Value Source # | |
ToValue a => ToValue [a] Source # | |
Defined in Data.PackStream.Internal.Type | |
ToValue a => ToValue (Map Text a) Source # | |
class FromValue a where Source #
The data types taht can be read from PackStream
representation
fromValue :: Value -> Either PackStreamError a Source #
Converts generic Value
type to a specific one or raises PackStreamError
Instances
FromValue Bool Source # | |
Defined in Data.PackStream.Internal.Type | |
FromValue Double Source # | |
Defined in Data.PackStream.Internal.Type | |
FromValue Int Source # | |
Defined in Data.PackStream.Internal.Type | |
FromValue Integer Source # | |
Defined in Data.PackStream.Internal.Type | |
FromValue () Source # | |
Defined in Data.PackStream.Internal.Type | |
FromValue ByteString Source # | |
Defined in Data.PackStream.Internal.Type | |
FromValue Text Source # | |
Defined in Data.PackStream.Internal.Type | |
FromValue Structure Source # | |
Defined in Data.PackStream.Internal.Type | |
FromValue Value Source # | |
Defined in Data.PackStream.Internal.Type | |
FromValue a => FromValue [a] Source # | |
Defined in Data.PackStream.Internal.Type | |
FromValue a => FromValue (Map Text a) Source # | |
Defined in Data.PackStream.Internal.Type |
(=:) :: ToValue a => Text -> a -> (Text, Value) Source #
Represent a Text
key and some ToValue
data into the Map
pair.
Can be useful to work with PackStream
dictionaries.
fromList ["hello" =: 1, "world" =: False]
at :: (MonadError PackStreamError m, FromValue a) => Map Text Value -> Text -> m a Source #
Extract a value of a specific type from Value
dictionary
A structure is a composite value, comprised of fields and a unique type code. Structure encodings consist, beyond the marker, of a single byte, the tag byte, followed by a sequence of up to 15 fields, each an individual value. The size of a structure is measured as the number of fields and not the total byte size. This count does not include the tag.