| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Text.ProtocolBuffers.Basic
Contents
Description
- data Double :: *
- data Float :: *
- data Bool :: *
- data Maybe a :: * -> *
- data Seq a :: * -> *
- newtype Utf8 = Utf8 ByteString
- data ByteString :: *
- data Int32 :: *
- data Int64 :: *
- data Word32 :: *
- data Word64 :: *
- newtype WireTag = WireTag {- getWireTag :: Word32
 
- newtype FieldId = FieldId {- getFieldId :: Int32
 
- newtype WireType = WireType {}
- newtype FieldType = FieldType {- getFieldType :: Int
 
- newtype EnumCode = EnumCode {- getEnumCode :: Int32
 
- type WireSize = Int64
- class Default a => Mergeable a where
- class Default a where
- isValidUTF8 :: ByteString -> Maybe Int
- toUtf8 :: ByteString -> Either Int Utf8
- utf8 :: Utf8 -> ByteString
- uToString :: Utf8 -> String
- uFromString :: String -> Utf8
Basic types for protocol buffer fields in Haskell
Double-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE double-precision type.
Instances
| Eq Double | |
| Floating Double | |
| Data Double | |
| Ord Double | |
| Read Double | |
| RealFloat Double | |
| PrintfArg Double | |
| Storable Double | |
| Default Double Source # | |
| Mergeable Double Source # | |
| TextType Double Source # | |
| Wire Double Source # | |
| GPB Double Source # | |
| IArray UArray Double | |
| MessageAPI msg (msg -> Double) Double Source # | |
| Functor (URec Double) | |
| Foldable (URec Double) | |
| Traversable (URec Double) | |
| Generic1 (URec Double) | |
| MArray (STUArray s) Double (ST s) | |
| Eq (URec Double p) | |
| Ord (URec Double p) | |
| Show (URec Double p) | |
| Generic (URec Double p) | |
| data URec Double | Used for marking occurrences of  | 
| type Rep1 (URec Double) | |
| type Rep (URec Double p) | |
Single-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE single-precision type.
Instances
| Eq Float | |
| Floating Float | |
| Data Float | |
| Ord Float | |
| Read Float | |
| RealFloat Float | |
| PrintfArg Float | |
| Storable Float | |
| Default Float Source # | |
| Mergeable Float Source # | |
| TextType Float Source # | |
| Wire Float Source # | |
| GPB Float Source # | |
| IArray UArray Float | |
| MessageAPI msg (msg -> Float) Float Source # | |
| Functor (URec Float) | |
| Foldable (URec Float) | |
| Traversable (URec Float) | |
| Generic1 (URec Float) | |
| MArray (STUArray s) Float (ST s) | |
| Eq (URec Float p) | |
| Ord (URec Float p) | |
| Show (URec Float p) | |
| Generic (URec Float p) | |
| data URec Float | Used for marking occurrences of  | 
| type Rep1 (URec Float) | |
| type Rep (URec Float p) | |
Instances
| Bounded Bool | |
| Enum Bool | |
| Eq Bool | |
| Data Bool | |
| Ord Bool | |
| Read Bool | |
| Show Bool | |
| Ix Bool | |
| Generic Bool | |
| Storable Bool | |
| Bits Bool | |
| FiniteBits Bool | |
| Default Bool Source # | |
| Mergeable Bool Source # | |
| TextType Bool Source # | |
| Wire Bool Source # | |
| GPB Bool Source # | |
| IArray UArray Bool | |
| SingI Bool False | |
| SingI Bool True | |
| SingKind Bool (KProxy Bool) | |
| MArray (STUArray s) Bool (ST s) | |
| type Rep Bool | |
| data Sing Bool | |
| type (==) Bool a b | |
| type DemoteRep Bool (KProxy Bool) | |
The Maybe type encapsulates an optional value.  A value of type
 Maybe aa (represented as Just aNothing).  Using Maybe is a good way to
 deal with errors or exceptional cases without resorting to drastic
 measures such as error.
The Maybe type is also a monad.  It is a simple kind of error
 monad, where all errors are represented by Nothing.  A richer
 error monad can be built using the Either type.
Instances
| Monad Maybe | |
| Functor Maybe | |
| Applicative Maybe | |
| Foldable Maybe | |
| Traversable Maybe | |
| Generic1 Maybe | |
| Eq1 Maybe | |
| Ord1 Maybe | |
| Read1 Maybe | |
| Show1 Maybe | |
| Alternative Maybe | |
| MonadPlus Maybe | |
| ExtKey Maybe Source # | |
| (Default msg, Default a) => MessageAPI msg (msg -> Maybe a) a Source # | |
| Default v => MessageAPI msg (Key Maybe msg v) v Source # | |
| Eq a => Eq (Maybe a) | |
| Data a => Data (Maybe a) | |
| Ord a => Ord (Maybe a) | |
| Read a => Read (Maybe a) | |
| Show a => Show (Maybe a) | |
| Generic (Maybe a) | |
| Semigroup a => Semigroup (Maybe a) | |
| Monoid a => Monoid (Maybe a) | Lift a semigroup into  | 
| Default (Maybe a) Source # | |
| Mergeable a => Mergeable (Maybe a) Source # | |
| TextType a => TextType (Maybe a) Source # | |
| SingI (Maybe a) (Nothing a) | |
| SingKind a (KProxy a) => SingKind (Maybe a) (KProxy (Maybe a)) | |
| SingI a a1 => SingI (Maybe a) (Just a a1) | |
| type Rep1 Maybe | |
| type Rep (Maybe a) | |
| data Sing (Maybe a) | |
| type (==) (Maybe k) a b | |
| type DemoteRep (Maybe a) (KProxy (Maybe a)) | |
General-purpose finite sequences.
Instances
| Monad Seq | |
| Functor Seq | |
| Applicative Seq | |
| Foldable Seq | |
| Traversable Seq | |
| Alternative Seq | |
| MonadPlus Seq | |
| ExtKey Seq Source # | |
| MessageAPI msg (msg -> Seq a) (Seq a) Source # | |
| Default v => MessageAPI msg (Key Seq msg v) (Seq v) Source # | |
| IsList (Seq a) | |
| Eq a => Eq (Seq a) | |
| Data a => Data (Seq a) | |
| Ord a => Ord (Seq a) | |
| Read a => Read (Seq a) | |
| Show a => Show (Seq a) | |
| IsString (Seq Char) | |
| Semigroup (Seq a) | |
| Monoid (Seq a) | |
| NFData a => NFData (Seq a) | |
| Default (Seq a) Source # | |
| Mergeable (Seq a) Source # | |
| TextType a => TextType (Seq a) Source # | |
| type Item (Seq a) | |
Utf8 is used to mark ByteString values that (should) contain
 valid utf8 encoded strings.  This type is used to represent
 TYPE_STRING values.
Constructors
| Utf8 ByteString | 
Instances
| Eq Utf8 Source # | |
| Data Utf8 Source # | |
| Ord Utf8 Source # | |
| Read Utf8 Source # | |
| Show Utf8 Source # | |
| Monoid Utf8 Source # | |
| Default Utf8 Source # | |
| Mergeable Utf8 Source # | |
| Dotted Utf8 Source # | |
| TextType Utf8 Source # | |
| Wire Utf8 Source # | |
| GPB Utf8 Source # | |
| MessageAPI msg (msg -> Utf8) Utf8 Source # | |
| Mangle (FIName Utf8) (PFName String) Source # | |
| Mangle (FIName Utf8) (PMName String) Source # | |
| Mangle (DIName Utf8) (PFName String) Source # | |
| Mangle (DIName Utf8) (PMName String) Source # | |
| Mangle (IName Utf8) (FName String) Source # | |
| Mangle (IName Utf8) (MName String) Source # | |
data ByteString :: * #
A space-efficient representation of a Word8 vector, supporting many
 efficient operations.
A lazy ByteString contains 8-bit bytes, or by using the operations
 from Data.ByteString.Lazy.Char8 it can be interpreted as containing
 8-bit characters.
Instances
32-bit signed integer type
Instances
| Bounded Int32 | |
| Enum Int32 | |
| Eq Int32 | |
| Integral Int32 | |
| Data Int32 | |
| Num Int32 | |
| Ord Int32 | |
| Read Int32 | |
| Real Int32 | |
| Show Int32 | |
| Ix Int32 | |
| PrintfArg Int32 | |
| Storable Int32 | |
| Bits Int32 | |
| FiniteBits Int32 | |
| Default Int32 Source # | |
| Mergeable Int32 Source # | |
| TextType Int32 Source # | |
| Wire Int32 Source # | |
| GPB Int32 Source # | |
| IArray UArray Int32 | |
| MessageAPI msg (msg -> Int32) Int32 Source # | |
| MArray (STUArray s) Int32 (ST s) | |
64-bit signed integer type
Instances
| Bounded Int64 | |
| Enum Int64 | |
| Eq Int64 | |
| Integral Int64 | |
| Data Int64 | |
| Num Int64 | |
| Ord Int64 | |
| Read Int64 | |
| Real Int64 | |
| Show Int64 | |
| Ix Int64 | |
| PrintfArg Int64 | |
| Storable Int64 | |
| Bits Int64 | |
| FiniteBits Int64 | |
| Default Int64 Source # | |
| Mergeable Int64 Source # | |
| TextType Int64 Source # | |
| Wire Int64 Source # | |
| GPB Int64 Source # | |
| IArray UArray Int64 | |
| MessageAPI msg (msg -> Int64) Int64 Source # | |
| MArray (STUArray s) Int64 (ST s) | |
32-bit unsigned integer type
Instances
64-bit unsigned integer type
Instances
Haskell types that act in the place of DescritorProto values
WireTag is the 32 bit value with the upper 29 bits being the
 FieldId and the lower 3 bits being the WireType
Constructors
| WireTag | |
| Fields 
 | |
FieldId is the field number which can be in the range 1 to
 2^29-1 but the value from 19000 to 19999 are forbidden (so sayeth
 Google).
Constructors
| FieldId | |
| Fields 
 | |
WireType is the 3 bit wire encoding value, and is currently in
 the range 0 to 5, leaving 6 and 7 currently invalid.
- 0 Varint : int32, int64, uint32, uint64, sint32, sint64, bool, enum
- 1 64-bit : fixed64, sfixed64, double
- 2 Length-delimited : string, bytes, embedded messages
- 3 Start group : groups (deprecated)
- 4 End group : groups (deprecated)
- 5 32-bit : fixed32, sfixed32, float
Constructors
| WireType | |
| Fields | |
FieldType is the integer associated with the
  FieldDescriptorProto's Type.  The allowed range is currently 1 to
  18, as shown below (excerpt from descritor.proto)
   // 0 is reserved for errors.
   // Order is weird for historical reasons.
   TYPE_DOUBLE         = 1;
   TYPE_FLOAT          = 2;
   TYPE_INT64          = 3;   // Not ZigZag encoded.  Negative numbers
                              // take 10 bytes.  Use TYPE_SINT64 if negative
                              // values are likely.
   TYPE_UINT64         = 4;
   TYPE_INT32          = 5;   // Not ZigZag encoded.  Negative numbers
                              // take 10 bytes.  Use TYPE_SINT32 if negative
                              // values are likely.
   TYPE_FIXED64        = 6;
   TYPE_FIXED32        = 7;
   TYPE_BOOL           = 8;
   TYPE_STRING         = 9;
   TYPE_GROUP          = 10;  // Tag-delimited aggregate.
   TYPE_MESSAGE        = 11;  // Length-delimited aggregate.
   // New in version 2.
   TYPE_BYTES          = 12;
   TYPE_UINT32         = 13;
   TYPE_ENUM           = 14;
   TYPE_SFIXED32       = 15;
   TYPE_SFIXED64       = 16;
   TYPE_SINT32         = 17;  // Uses ZigZag encoding.
   TYPE_SINT64         = 18;  // Uses ZigZag encoding.Constructors
| FieldType | |
| Fields 
 | |
EnumCode is the Int32 assoicated with a
 EnumValueDescriptorProto and is in the range 0 to 2^31-1.
Constructors
| EnumCode | |
| Fields 
 | |
type WireSize = Int64 Source #
WireSize is the Int64 size type associated with the lazy
 bytestrings used in the Put and Get monads.
Some of the type classes implemented messages and fields
class Default a => Mergeable a where Source #
The Mergeable class is not a Monoid, mergeEmpty is not a
 left or right unit like mempty.  The default mergeAppend is to
 take the second parameter and discard the first one.  The
 mergeConcat defaults to foldl associativity.
NOTE: mergeEmpty has been removed in protocol buffers version 2.
 Use defaultValue instead.  New strict fields would mean that required
 fields in messages will be automatic errors with mergeEmpty.
Methods
mergeAppend :: a -> a -> a Source #
mergeAppend is the right-biased merge of two values.  A
 message (or group) is merged recursively.  Required field are
 always taken from the second message. Optional field values are
 taken from the most defined message or the second message if
 both are set.  Repeated fields have the sequences concatenated.
 Note that strings and bytes are NOT concatenated.
mergeConcat :: Foldable t => t a -> a Source #
mergeConcat is  F.foldl mergeAppend defaultValue  and this
 default definition is not overridden in any of the code except
 for the (Seq a) instance.
Instances
class Default a where Source #
The Default class has the default-default values of types.  See
 http://code.google.com/apis/protocolbuffers/docs/proto.html#optional
 and also note that Enum types have a defaultValue that is the
 first one in the .proto file (there is always at least one
 value).  Instances of this for messages hold any default value
 defined in the .proto file.  defaultValue is where the
 MessageAPI function getVal looks when an optional field is not
 set.
Minimal complete definition
Methods
defaultValue :: a Source #
The defaultValue is never undefined or an error to evalute.
 This makes it much more useful compared to mergeEmpty. In a
 default message all Optional field values are set to Nothing
 and Repeated field values are empty.
Instances
isValidUTF8 :: ByteString -> Maybe Int Source #
utf8 :: Utf8 -> ByteString Source #
uFromString :: String -> Utf8 Source #