Z-MessagePack-0.3.0.0: MessagePack
Copyright(c) Hideyuki Tanaka 2009-2015
(c) Dong Han 2020
LicenseBSD3
Safe HaskellNone
LanguageHaskell2010

Z.Data.MessagePack.Value

Description

 
Synopsis

MessagePack Value

data Value Source #

Representation of MessagePack data.

Constructors

Bool !Bool

true or false

Int !Int64

an integer

Float !Float

a floating point number

Double !Double

a floating point number

Str !Text

a UTF-8 string

Bin !Bytes

a byte array

Array !(Vector Value)

a sequence of objects

Map !(Vector (Value, Value))

key-value pairs of objects

Ext 

Fields

Nil

nil

Instances

Instances details
Eq Value Source # 
Instance details

Defined in Z.Data.MessagePack.Value

Methods

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

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

Ord Value Source # 
Instance details

Defined in Z.Data.MessagePack.Value

Methods

compare :: Value -> Value -> Ordering #

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

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

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

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

max :: Value -> Value -> Value #

min :: Value -> Value -> Value #

Show Value Source # 
Instance details

Defined in Z.Data.MessagePack.Value

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

Generic Value Source # 
Instance details

Defined in Z.Data.MessagePack.Value

Associated Types

type Rep Value :: Type -> Type #

Methods

from :: Value -> Rep Value x #

to :: Rep Value x -> Value #

Arbitrary Value Source # 
Instance details

Defined in Z.Data.MessagePack.Value

Methods

arbitrary :: Gen Value #

shrink :: Value -> [Value] #

Print Value Source # 
Instance details

Defined in Z.Data.MessagePack.Value

Methods

toUTF8BuilderP :: Int -> Value -> Builder () #

NFData Value Source # 
Instance details

Defined in Z.Data.MessagePack.Value

Methods

rnf :: Value -> () #

MessagePack Value Source # 
Instance details

Defined in Z.Data.MessagePack.Base

type Rep Value Source # 
Instance details

Defined in Z.Data.MessagePack.Value

type Rep Value = D1 ('MetaData "Value" "Z.Data.MessagePack.Value" "Z-MessagePack-0.3.0.0-7KvFiOecrsnKr7xFC1c8Fa" 'False) (((C1 ('MetaCons "Bool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :+: C1 ('MetaCons "Int" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int64))) :+: (C1 ('MetaCons "Float" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Float)) :+: (C1 ('MetaCons "Double" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Double)) :+: C1 ('MetaCons "Str" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Text))))) :+: ((C1 ('MetaCons "Bin" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Bytes)) :+: C1 ('MetaCons "Array" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 (Vector Value)))) :+: (C1 ('MetaCons "Map" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 (Vector (Value, Value)))) :+: (C1 ('MetaCons "Ext" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word8) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Bytes)) :+: C1 ('MetaCons "Nil" 'PrefixI 'False) (U1 :: Type -> Type)))))

parse into MessagePack Value

parseValue :: Bytes -> (Bytes, Either ParseError Value) Source #

Parse Value without consuming trailing bytes.

parseValue' :: Bytes -> Either ParseError Value Source #

Parse Value, if there're bytes left, parsing will fail.

parseValueChunks :: Monad m => m Bytes -> Bytes -> m (Bytes, Either ParseError Value) Source #

Increamental parse Value without consuming trailing bytes.

parseValueChunks' :: Monad m => m Bytes -> Bytes -> m (Either ParseError Value) Source #

Increamental parse Value, if there're bytes left, parsing will fail.

Value Parsers