packstream-0.1.0.0: PackStream converter for Neo4j BOLT protocol
Safe HaskellNone
LanguageHaskell2010

Data.PackStream.Internal.Type

Synopsis

PackStream basics

data PackStreamError Source #

Basic PackStream error type that is used to handle parsing errors.

Constructors

NotNull

This ByteString doesn't represent null object

NotBool

This ByteString doesn't represent any boolean

NotWord

This ByteString doesn't represent any unsigned integer

NotInt

This ByteString doesn't represent any integer

NotFloat

This ByteString doesn't represent any floating-point number

NotString

This ByteString doesn't represent any Text string

NotBytes

This ByteString doesn't represent any ByteString array

NotList

This ByteString doesn't represent any list of PackStream values

NotDict

This ByteString doesn't represent any dictionary of PackStream values

NotStructure

This ByteString doesn't represent any Structure

NotValue

This ByteString doesn't represent any Value

WrongStructure Text

This ByteString doesn't represent specific Structure

newtype PackStream a Source #

Basic parser type. It works like parser combinators for binary data that represents PackStream.

Instances

Instances details
Monad PackStream Source # 
Instance details

Defined in Data.PackStream.Internal.Type

Methods

(>>=) :: PackStream a -> (a -> PackStream b) -> PackStream b #

(>>) :: PackStream a -> PackStream b -> PackStream b #

return :: a -> PackStream a #

Functor PackStream Source # 
Instance details

Defined in Data.PackStream.Internal.Type

Methods

fmap :: (a -> b) -> PackStream a -> PackStream b #

(<$) :: a -> PackStream b -> PackStream a #

Applicative PackStream Source # 
Instance details

Defined in Data.PackStream.Internal.Type

Methods

pure :: a -> PackStream a #

(<*>) :: PackStream (a -> b) -> PackStream a -> PackStream b #

liftA2 :: (a -> b -> c) -> PackStream a -> PackStream b -> PackStream c #

(*>) :: PackStream a -> PackStream b -> PackStream b #

(<*) :: PackStream a -> PackStream b -> PackStream a #

MonadState ByteString PackStream Source # 
Instance details

Defined in Data.PackStream.Internal.Type

MonadError PackStreamError PackStream Source # 
Instance details

Defined in Data.PackStream.Internal.Type

unpackStream :: PackStream a -> ByteString -> Either PackStreamError a Source #

Use specific parser combinator to parse the ByteString that represents any PackStream data.

data Value Source #

PackStream offers a number of core data types, many supported by multiple binary representations, as well as a flexible extension mechanism.

Constructors

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 Values

D (Map Text Value)

Collection of key-value entries (no order guaranteed)

S Structure

Composite value with a type signature

Instances

Instances details
Eq Value Source # 
Instance details

Defined in Data.PackStream.Internal.Type

Methods

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

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

Show Value Source # 
Instance details

Defined in Data.PackStream.Internal.Type

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

FromValue Value Source # 
Instance details

Defined in Data.PackStream.Internal.Type

ToValue Value Source # 
Instance details

Defined in Data.PackStream.Internal.Type

Methods

toValue :: Value -> Value Source #

PackStreamValue Value Source # 
Instance details

Defined in Data.PackStream

data Structure Source #

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.

Constructors

Structure 

Fields

class ToValue a where Source #

The data types that can be serialized as PackStream

Methods

toValue :: a -> Value Source #

Convert data type to the generic Value

Instances

Instances details
ToValue Bool Source # 
Instance details

Defined in Data.PackStream.Internal.Type

Methods

toValue :: Bool -> Value Source #

ToValue Double Source # 
Instance details

Defined in Data.PackStream.Internal.Type

Methods

toValue :: Double -> Value Source #

ToValue Int Source # 
Instance details

Defined in Data.PackStream.Internal.Type

Methods

toValue :: Int -> Value Source #

ToValue Integer Source # 
Instance details

Defined in Data.PackStream.Internal.Type

ToValue () Source # 
Instance details

Defined in Data.PackStream.Internal.Type

Methods

toValue :: () -> Value Source #

ToValue ByteString Source # 
Instance details

Defined in Data.PackStream.Internal.Type

ToValue Text Source # 
Instance details

Defined in Data.PackStream.Internal.Type

Methods

toValue :: Text -> Value Source #

ToValue Structure Source # 
Instance details

Defined in Data.PackStream.Internal.Type

ToValue Value Source # 
Instance details

Defined in Data.PackStream.Internal.Type

Methods

toValue :: Value -> Value Source #

ToValue a => ToValue [a] Source # 
Instance details

Defined in Data.PackStream.Internal.Type

Methods

toValue :: [a] -> Value Source #

ToValue a => ToValue (Map Text a) Source # 
Instance details

Defined in Data.PackStream.Internal.Type

Methods

toValue :: Map Text a -> Value Source #

(=:) :: 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]

class FromValue a where Source #

The data types taht can be read from PackStream representation

Methods

fromValue :: Value -> Either PackStreamError a Source #

Converts generic Value type to a specific one or raises PackStreamError

Instances

Instances details
FromValue Bool Source # 
Instance details

Defined in Data.PackStream.Internal.Type

FromValue Double Source # 
Instance details

Defined in Data.PackStream.Internal.Type

FromValue Int Source # 
Instance details

Defined in Data.PackStream.Internal.Type

FromValue Integer Source # 
Instance details

Defined in Data.PackStream.Internal.Type

FromValue () Source # 
Instance details

Defined in Data.PackStream.Internal.Type

FromValue ByteString Source # 
Instance details

Defined in Data.PackStream.Internal.Type

FromValue Text Source # 
Instance details

Defined in Data.PackStream.Internal.Type

FromValue Structure Source # 
Instance details

Defined in Data.PackStream.Internal.Type

FromValue Value Source # 
Instance details

Defined in Data.PackStream.Internal.Type

FromValue a => FromValue [a] Source # 
Instance details

Defined in Data.PackStream.Internal.Type

FromValue a => FromValue (Map Text a) Source # 
Instance details

Defined in Data.PackStream.Internal.Type