protocol-buffers-2.4.17: Parse Google Protocol Buffer specifications
Safe HaskellNone
LanguageHaskell2010

Text.ProtocolBuffers

Description

Text.ProtocolBuffers exposes the client API. This merely re-exports parts of the other modules in protocol-buffers. The exposed parts are:

import Text.ProtocolBuffers.Basic
  ( Seq,isValidUTF8,toUtf8,utf8,Utf8(Utf8),Int32,Int64,Word32,Word64
  , WireTag,FieldId,WireType,FieldType,EnumCode,WireSize
  , Mergeable(mergeAppend,mergeConcat),Default(defaultValue))
import Text.ProtocolBuffers.Extensions
  ( Key,ExtKey(getExt,putExt,clearExt),MessageAPI(getVal,isSet)
  , getKeyFieldId,getKeyFieldType,getKeyDefaultValue)
import Text.ProtocolBuffers.Identifiers
import Text.ProtocolBuffers.Reflections
  ( ReflectDescriptor(..),ReflectEnum(..),ProtoName(..),HsDefault(..),EnumInfoApp
  , KeyInfo,FieldInfo(..),DescriptorInfo(..),EnumInfo(..),ProtoInfo(..),makePNF )
import Text.ProtocolBuffers.TextMessage
  ( messagePutText, messageGetText )
import Text.ProtocolBuffers.WireMessage
  ( Wire,Put,Get,runPut,runGet,runGetOnLazy
  , messageSize,messagePut,messageGet,messagePutM,messageGetM
  , messageWithLengthSize,messageWithLengthPut,messageWithLengthGet,messageWithLengthPutM,messageWithLengthGetM
  , messageAsFieldSize,messageAsFieldPutM,messageAsFieldGetM)

The message serialization is taken care of by WireMessage operations, especially messagePut and messageGet. The MessageAPI provides the useful polymorphic getVal and isSet where getVal looks up default values and also works with extension keys. The Utf8 newtype is used to indicate the format in the underlying lazy ByteString. Messages and values can be combined with the right-biased Mergeable operations. The mergeEmpty should not be used as required values are filled in with undefined errors, please use defaultValue instead.

The Utf8 type is a newtype of the Lazy ByteString. It can be safely constructed by checking for errors with toUtf8, which returns 'Left Int' indicating the index where an error is detected. It can be deconstructed with utf8.

Synopsis

Documentation

data Int32 #

32-bit signed integer type

Instances

Instances details
Bounded Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Eq Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

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

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

Integral Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Data Int32

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int32 -> c Int32 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int32 #

toConstr :: Int32 -> Constr #

dataTypeOf :: Int32 -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Int32) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int32) #

gmapT :: (forall b. Data b => b -> b) -> Int32 -> Int32 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int32 -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int32 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Int32 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Int32 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int32 -> m Int32 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int32 -> m Int32 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int32 -> m Int32 #

Num Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Ord Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

compare :: Int32 -> Int32 -> Ordering #

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

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

(>) :: Int32 -> Int32 -> Bool #

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

max :: Int32 -> Int32 -> Int32 #

min :: Int32 -> Int32 -> Int32 #

Read Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Real Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

toRational :: Int32 -> Rational #

Show Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int32 -> ShowS #

show :: Int32 -> String #

showList :: [Int32] -> ShowS #

Ix Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Hashable Int32 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int32 -> Int #

hash :: Int32 -> Int #

ToJSON Int32 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Int32 
Instance details

Defined in Data.Aeson.Types.ToJSON

FromJSON Int32 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Int32 
Instance details

Defined in Data.Aeson.Types.FromJSON

PrintfArg Int32

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Int32

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int32 -> Int #

alignment :: Int32 -> Int #

peekElemOff :: Ptr Int32 -> Int -> IO Int32 #

pokeElemOff :: Ptr Int32 -> Int -> Int32 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int32 #

pokeByteOff :: Ptr b -> Int -> Int32 -> IO () #

peek :: Ptr Int32 -> IO Int32 #

poke :: Ptr Int32 -> Int32 -> IO () #

Bits Int32

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBits Int32

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

Unbox Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

Default Int32 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Mergeable Int32 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

TextType Int32 Source # 
Instance details

Defined in Text.ProtocolBuffers.TextMessage

Methods

tellT :: String -> Int32 -> Output Source #

getT :: Stream s Identity Char => String -> Parsec s () Int32 Source #

Wire Int32 Source # 
Instance details

Defined in Text.ProtocolBuffers.WireMessage

GPB Int32 Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

IArray UArray Int32 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i Int32 -> (i, i) #

numElements :: Ix i => UArray i Int32 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Int32)] -> UArray i Int32

unsafeAt :: Ix i => UArray i Int32 -> Int -> Int32

unsafeReplace :: Ix i => UArray i Int32 -> [(Int, Int32)] -> UArray i Int32

unsafeAccum :: Ix i => (Int32 -> e' -> Int32) -> UArray i Int32 -> [(Int, e')] -> UArray i Int32

unsafeAccumArray :: Ix i => (Int32 -> e' -> Int32) -> Int32 -> (i, i) -> [(Int, e')] -> UArray i Int32

Vector Vector Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

MessageAPI msg (msg -> Int32) Int32 Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

Methods

getVal :: msg -> (msg -> Int32) -> Int32 Source #

isSet :: msg -> (msg -> Int32) -> Bool Source #

MArray (STUArray s) Int32 (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i Int32 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Int32 -> ST s Int

newArray :: Ix i => (i, i) -> Int32 -> ST s (STUArray s i Int32) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int32) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int32)

unsafeRead :: Ix i => STUArray s i Int32 -> Int -> ST s Int32

unsafeWrite :: Ix i => STUArray s i Int32 -> Int -> Int32 -> ST s ()

newtype Vector Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

data Int64 #

64-bit signed integer type

Instances

Instances details
Bounded Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Eq Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

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

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

Integral Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Data Int64

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int64 -> c Int64 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int64 #

toConstr :: Int64 -> Constr #

dataTypeOf :: Int64 -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Int64) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int64) #

gmapT :: (forall b. Data b => b -> b) -> Int64 -> Int64 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int64 -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int64 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Int64 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Int64 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int64 -> m Int64 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int64 -> m Int64 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int64 -> m Int64 #

Num Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Ord Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

compare :: Int64 -> Int64 -> Ordering #

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

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

(>) :: Int64 -> Int64 -> Bool #

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

max :: Int64 -> Int64 -> Int64 #

min :: Int64 -> Int64 -> Int64 #

Read Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Real Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

toRational :: Int64 -> Rational #

Show Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int64 -> ShowS #

show :: Int64 -> String #

showList :: [Int64] -> ShowS #

Ix Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Hashable Int64 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int64 -> Int #

hash :: Int64 -> Int #

ToJSON Int64 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Int64 
Instance details

Defined in Data.Aeson.Types.ToJSON

FromJSON Int64 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Int64 
Instance details

Defined in Data.Aeson.Types.FromJSON

PrintfArg Int64

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Int64

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int64 -> Int #

alignment :: Int64 -> Int #

peekElemOff :: Ptr Int64 -> Int -> IO Int64 #

pokeElemOff :: Ptr Int64 -> Int -> Int64 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int64 #

pokeByteOff :: Ptr b -> Int -> Int64 -> IO () #

peek :: Ptr Int64 -> IO Int64 #

poke :: Ptr Int64 -> Int64 -> IO () #

Bits Int64

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBits Int64

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

Unbox Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

Default Int64 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Mergeable Int64 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

TextType Int64 Source # 
Instance details

Defined in Text.ProtocolBuffers.TextMessage

Methods

tellT :: String -> Int64 -> Output Source #

getT :: Stream s Identity Char => String -> Parsec s () Int64 Source #

Wire Int64 Source # 
Instance details

Defined in Text.ProtocolBuffers.WireMessage

GPB Int64 Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

IArray UArray Int64 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i Int64 -> (i, i) #

numElements :: Ix i => UArray i Int64 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Int64)] -> UArray i Int64

unsafeAt :: Ix i => UArray i Int64 -> Int -> Int64

unsafeReplace :: Ix i => UArray i Int64 -> [(Int, Int64)] -> UArray i Int64

unsafeAccum :: Ix i => (Int64 -> e' -> Int64) -> UArray i Int64 -> [(Int, e')] -> UArray i Int64

unsafeAccumArray :: Ix i => (Int64 -> e' -> Int64) -> Int64 -> (i, i) -> [(Int, e')] -> UArray i Int64

Vector Vector Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

MessageAPI msg (msg -> Int64) Int64 Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

Methods

getVal :: msg -> (msg -> Int64) -> Int64 Source #

isSet :: msg -> (msg -> Int64) -> Bool Source #

MArray (STUArray s) Int64 (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i Int64 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Int64 -> ST s Int

newArray :: Ix i => (i, i) -> Int64 -> ST s (STUArray s i Int64) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int64) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int64)

unsafeRead :: Ix i => STUArray s i Int64 -> Int -> ST s Int64

unsafeWrite :: Ix i => STUArray s i Int64 -> Int -> Int64 -> ST s ()

newtype Vector Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

data Word32 #

32-bit unsigned integer type

Instances

Instances details
Bounded Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Eq Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

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

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

Integral Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Data Word32

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word32 -> c Word32 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word32 #

toConstr :: Word32 -> Constr #

dataTypeOf :: Word32 -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Word32) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word32) #

gmapT :: (forall b. Data b => b -> b) -> Word32 -> Word32 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word32 -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word32 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Word32 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Word32 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word32 -> m Word32 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word32 -> m Word32 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word32 -> m Word32 #

Num Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Read Word32

Since: base-2.1

Instance details

Defined in GHC.Read

Real Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Ix Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Hashable Word32 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word32 -> Int #

hash :: Word32 -> Int #

ToJSON Word32 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Word32 
Instance details

Defined in Data.Aeson.Types.ToJSON

FromJSON Word32 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Word32 
Instance details

Defined in Data.Aeson.Types.FromJSON

PrintfArg Word32

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Word32

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Word32

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word32

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

Unbox Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

Default Word32 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Mergeable Word32 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

TextType Word32 Source # 
Instance details

Defined in Text.ProtocolBuffers.TextMessage

Methods

tellT :: String -> Word32 -> Output Source #

getT :: Stream s Identity Char => String -> Parsec s () Word32 Source #

Wire Word32 Source # 
Instance details

Defined in Text.ProtocolBuffers.WireMessage

GPB Word32 Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

IArray UArray Word32 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i Word32 -> (i, i) #

numElements :: Ix i => UArray i Word32 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Word32)] -> UArray i Word32

unsafeAt :: Ix i => UArray i Word32 -> Int -> Word32

unsafeReplace :: Ix i => UArray i Word32 -> [(Int, Word32)] -> UArray i Word32

unsafeAccum :: Ix i => (Word32 -> e' -> Word32) -> UArray i Word32 -> [(Int, e')] -> UArray i Word32

unsafeAccumArray :: Ix i => (Word32 -> e' -> Word32) -> Word32 -> (i, i) -> [(Int, e')] -> UArray i Word32

Vector Vector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

MessageAPI msg (msg -> Word32) Word32 Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

Methods

getVal :: msg -> (msg -> Word32) -> Word32 Source #

isSet :: msg -> (msg -> Word32) -> Bool Source #

MArray (STUArray s) Word32 (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i Word32 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Word32 -> ST s Int

newArray :: Ix i => (i, i) -> Word32 -> ST s (STUArray s i Word32) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word32) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word32)

unsafeRead :: Ix i => STUArray s i Word32 -> Int -> ST s Word32

unsafeWrite :: Ix i => STUArray s i Word32 -> Int -> Word32 -> ST s ()

newtype Vector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

data Word64 #

64-bit unsigned integer type

Instances

Instances details
Bounded Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Eq Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

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

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

Integral Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Data Word64

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word64 -> c Word64 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word64 #

toConstr :: Word64 -> Constr #

dataTypeOf :: Word64 -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Word64) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word64) #

gmapT :: (forall b. Data b => b -> b) -> Word64 -> Word64 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word64 -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word64 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Word64 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Word64 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word64 -> m Word64 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word64 -> m Word64 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word64 -> m Word64 #

Num Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Read Word64

Since: base-2.1

Instance details

Defined in GHC.Read

Real Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Ix Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Hashable Word64 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word64 -> Int #

hash :: Word64 -> Int #

ToJSON Word64 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Word64 
Instance details

Defined in Data.Aeson.Types.ToJSON

FromJSON Word64 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Word64 
Instance details

Defined in Data.Aeson.Types.FromJSON

PrintfArg Word64

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Word64

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Word64

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word64

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

Unbox Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

Default Word64 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Mergeable Word64 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

TextType Word64 Source # 
Instance details

Defined in Text.ProtocolBuffers.TextMessage

Methods

tellT :: String -> Word64 -> Output Source #

getT :: Stream s Identity Char => String -> Parsec s () Word64 Source #

Wire Word64 Source # 
Instance details

Defined in Text.ProtocolBuffers.WireMessage

GPB Word64 Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

IArray UArray Word64 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i Word64 -> (i, i) #

numElements :: Ix i => UArray i Word64 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Word64)] -> UArray i Word64

unsafeAt :: Ix i => UArray i Word64 -> Int -> Word64

unsafeReplace :: Ix i => UArray i Word64 -> [(Int, Word64)] -> UArray i Word64

unsafeAccum :: Ix i => (Word64 -> e' -> Word64) -> UArray i Word64 -> [(Int, e')] -> UArray i Word64

unsafeAccumArray :: Ix i => (Word64 -> e' -> Word64) -> Word64 -> (i, i) -> [(Int, e')] -> UArray i Word64

Vector Vector Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

MessageAPI msg (msg -> Word64) Word64 Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

Methods

getVal :: msg -> (msg -> Word64) -> Word64 Source #

isSet :: msg -> (msg -> Word64) -> Bool Source #

MArray (STUArray s) Word64 (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i Word64 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Word64 -> ST s Int

newArray :: Ix i => (i, i) -> Word64 -> ST s (STUArray s i Word64) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word64) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word64)

unsafeRead :: Ix i => STUArray s i Word64 -> Int -> ST s Word64

unsafeWrite :: Ix i => STUArray s i Word64 -> Int -> Word64 -> ST s ()

newtype Vector Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

data Seq a #

General-purpose finite sequences.

Instances

Instances details
Monad Seq 
Instance details

Defined in Data.Sequence.Internal

Methods

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

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

return :: a -> Seq a #

Functor Seq 
Instance details

Defined in Data.Sequence.Internal

Methods

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

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

MonadFix Seq

Since: containers-0.5.11

Instance details

Defined in Data.Sequence.Internal

Methods

mfix :: (a -> Seq a) -> Seq a #

Applicative Seq

Since: containers-0.5.4

Instance details

Defined in Data.Sequence.Internal

Methods

pure :: a -> Seq a #

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

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

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

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

Foldable Seq 
Instance details

Defined in Data.Sequence.Internal

Methods

fold :: Monoid m => Seq m -> m #

foldMap :: Monoid m => (a -> m) -> Seq a -> m #

foldMap' :: Monoid m => (a -> m) -> Seq a -> m #

foldr :: (a -> b -> b) -> b -> Seq a -> b #

foldr' :: (a -> b -> b) -> b -> Seq a -> b #

foldl :: (b -> a -> b) -> b -> Seq a -> b #

foldl' :: (b -> a -> b) -> b -> Seq a -> b #

foldr1 :: (a -> a -> a) -> Seq a -> a #

foldl1 :: (a -> a -> a) -> Seq a -> a #

toList :: Seq a -> [a] #

null :: Seq a -> Bool #

length :: Seq a -> Int #

elem :: Eq a => a -> Seq a -> Bool #

maximum :: Ord a => Seq a -> a #

minimum :: Ord a => Seq a -> a #

sum :: Num a => Seq a -> a #

product :: Num a => Seq a -> a #

Traversable Seq 
Instance details

Defined in Data.Sequence.Internal

Methods

traverse :: Applicative f => (a -> f b) -> Seq a -> f (Seq b) #

sequenceA :: Applicative f => Seq (f a) -> f (Seq a) #

mapM :: Monad m => (a -> m b) -> Seq a -> m (Seq b) #

sequence :: Monad m => Seq (m a) -> m (Seq a) #

ToJSON1 Seq 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Seq a -> Value #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Seq a] -> Value #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Seq a -> Encoding #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Seq a] -> Encoding #

FromJSON1 Seq 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Seq a) #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Seq a] #

Alternative Seq

Since: containers-0.5.4

Instance details

Defined in Data.Sequence.Internal

Methods

empty :: Seq a #

(<|>) :: Seq a -> Seq a -> Seq a #

some :: Seq a -> Seq [a] #

many :: Seq a -> Seq [a] #

MonadPlus Seq 
Instance details

Defined in Data.Sequence.Internal

Methods

mzero :: Seq a #

mplus :: Seq a -> Seq a -> Seq a #

Eq1 Seq

Since: containers-0.5.9

Instance details

Defined in Data.Sequence.Internal

Methods

liftEq :: (a -> b -> Bool) -> Seq a -> Seq b -> Bool #

Ord1 Seq

Since: containers-0.5.9

Instance details

Defined in Data.Sequence.Internal

Methods

liftCompare :: (a -> b -> Ordering) -> Seq a -> Seq b -> Ordering #

Read1 Seq

Since: containers-0.5.9

Instance details

Defined in Data.Sequence.Internal

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Seq a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Seq a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Seq a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Seq a] #

Show1 Seq

Since: containers-0.5.9

Instance details

Defined in Data.Sequence.Internal

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Seq a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Seq a] -> ShowS #

MonadZip Seq
 mzipWith = zipWith
 munzip = unzip
Instance details

Defined in Data.Sequence.Internal

Methods

mzip :: Seq a -> Seq b -> Seq (a, b) #

mzipWith :: (a -> b -> c) -> Seq a -> Seq b -> Seq c #

munzip :: Seq (a, b) -> (Seq a, Seq b) #

UnzipWith Seq 
Instance details

Defined in Data.Sequence.Internal

Methods

unzipWith' :: (x -> (a, b)) -> Seq x -> (Seq a, Seq b)

ExtKey Seq Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

Methods

putExt :: Key Seq msg v -> Seq v -> msg -> msg Source #

getExt :: Key Seq msg v -> msg -> Either String (Seq v) Source #

clearExt :: Key Seq msg v -> msg -> msg Source #

wireGetKey :: Key Seq msg v -> msg -> Get msg Source #

MessageAPI msg (msg -> Seq a) (Seq a) Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

Methods

getVal :: msg -> (msg -> Seq a) -> Seq a Source #

isSet :: msg -> (msg -> Seq a) -> Bool Source #

Default v => MessageAPI msg (Key Seq msg v) (Seq v) Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

Methods

getVal :: msg -> Key Seq msg v -> Seq v Source #

isSet :: msg -> Key Seq msg v -> Bool Source #

IsList (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Item (Seq a) #

Methods

fromList :: [Item (Seq a)] -> Seq a #

fromListN :: Int -> [Item (Seq a)] -> Seq a #

toList :: Seq a -> [Item (Seq a)] #

Eq a => Eq (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Methods

(==) :: Seq a -> Seq a -> Bool #

(/=) :: Seq a -> Seq a -> Bool #

Data a => Data (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Seq a -> c (Seq a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Seq a) #

toConstr :: Seq a -> Constr #

dataTypeOf :: Seq a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Seq a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Seq a)) #

gmapT :: (forall b. Data b => b -> b) -> Seq a -> Seq a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Seq a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Seq a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Seq a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Seq a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) #

Ord a => Ord (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Methods

compare :: Seq a -> Seq a -> Ordering #

(<) :: Seq a -> Seq a -> Bool #

(<=) :: Seq a -> Seq a -> Bool #

(>) :: Seq a -> Seq a -> Bool #

(>=) :: Seq a -> Seq a -> Bool #

max :: Seq a -> Seq a -> Seq a #

min :: Seq a -> Seq a -> Seq a #

Read a => Read (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Show a => Show (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Methods

showsPrec :: Int -> Seq a -> ShowS #

show :: Seq a -> String #

showList :: [Seq a] -> ShowS #

a ~ Char => IsString (Seq a)

Since: containers-0.5.7

Instance details

Defined in Data.Sequence.Internal

Methods

fromString :: String -> Seq a #

Semigroup (Seq a)

Since: containers-0.5.7

Instance details

Defined in Data.Sequence.Internal

Methods

(<>) :: Seq a -> Seq a -> Seq a #

sconcat :: NonEmpty (Seq a) -> Seq a #

stimes :: Integral b => b -> Seq a -> Seq a #

Monoid (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Methods

mempty :: Seq a #

mappend :: Seq a -> Seq a -> Seq a #

mconcat :: [Seq a] -> Seq a #

ToJSON a => ToJSON (Seq a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Seq a -> Value #

toEncoding :: Seq a -> Encoding #

toJSONList :: [Seq a] -> Value #

toEncodingList :: [Seq a] -> Encoding #

FromJSON a => FromJSON (Seq a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Seq a) #

parseJSONList :: Value -> Parser [Seq a] #

NFData a => NFData (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Methods

rnf :: Seq a -> () #

Default (Seq a) Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Methods

defaultValue :: Seq a Source #

Mergeable (Seq a) Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Methods

mergeAppend :: Seq a -> Seq a -> Seq a Source #

mergeConcat :: Foldable t => t (Seq a) -> Seq a Source #

TextType a => TextType (Seq a) Source # 
Instance details

Defined in Text.ProtocolBuffers.TextMessage

Methods

tellT :: String -> Seq a -> Output Source #

getT :: Stream s Identity Char => String -> Parsec s () (Seq a) Source #

type Item (Seq a) 
Instance details

Defined in Data.Sequence.Internal

type Item (Seq a) = a

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.

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

Instances details
Default Bool Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Default Double Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Default Float Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Default Int32 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Default Int64 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Default Word32 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Default Word64 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Default ByteString Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Default Utf8 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Default UnknownField Source # 
Instance details

Defined in Text.ProtocolBuffers.Unknown

Default ExtField Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

Default (Maybe a) Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Default (Seq a) Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Methods

defaultValue :: Seq a Source #

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.

Minimal complete definition

Nothing

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

Instances details
Mergeable Bool Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Mergeable Double Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Mergeable Float Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Mergeable Int32 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Mergeable Int64 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Mergeable Word32 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Mergeable Word64 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Mergeable ByteString Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Mergeable Utf8 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Mergeable UnknownField Source # 
Instance details

Defined in Text.ProtocolBuffers.Unknown

Mergeable ExtField Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

Mergeable a => Mergeable (Maybe a) Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Methods

mergeAppend :: Maybe a -> Maybe a -> Maybe a Source #

mergeConcat :: Foldable t => t (Maybe a) -> Maybe a Source #

Mergeable (Seq a) Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Methods

mergeAppend :: Seq a -> Seq a -> Seq a Source #

mergeConcat :: Foldable t => t (Seq a) -> Seq a Source #

type WireSize = Int64 Source #

WireSize is the Int64 size type associated with the lazy bytestrings used in the Put and Get monads.

data EnumCode Source #

EnumCode is the Int32 assoicated with a EnumValueDescriptorProto and is in the range 0 to 2^31-1.

Instances

Instances details
Bounded EnumCode Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Eq EnumCode Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Data EnumCode Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EnumCode -> c EnumCode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EnumCode #

toConstr :: EnumCode -> Constr #

dataTypeOf :: EnumCode -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EnumCode) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EnumCode) #

gmapT :: (forall b. Data b => b -> b) -> EnumCode -> EnumCode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EnumCode -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EnumCode -> r #

gmapQ :: (forall d. Data d => d -> u) -> EnumCode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EnumCode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EnumCode -> m EnumCode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EnumCode -> m EnumCode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EnumCode -> m EnumCode #

Num EnumCode Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Ord EnumCode Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Read EnumCode Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Show EnumCode Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

data FieldType Source #

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.

Instances

Instances details
Bounded FieldType Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Enum FieldType Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Eq FieldType Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Data FieldType Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldType -> c FieldType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FieldType #

toConstr :: FieldType -> Constr #

dataTypeOf :: FieldType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FieldType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FieldType) #

gmapT :: (forall b. Data b => b -> b) -> FieldType -> FieldType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldType -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldType -> r #

gmapQ :: (forall d. Data d => d -> u) -> FieldType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldType -> m FieldType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldType -> m FieldType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldType -> m FieldType #

Num FieldType Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Ord FieldType Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Read FieldType Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Show FieldType Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

data WireType Source #

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

Instances

Instances details
Bounded WireType Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Enum WireType Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Eq WireType Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Data WireType Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WireType -> c WireType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WireType #

toConstr :: WireType -> Constr #

dataTypeOf :: WireType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c WireType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WireType) #

gmapT :: (forall b. Data b => b -> b) -> WireType -> WireType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WireType -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WireType -> r #

gmapQ :: (forall d. Data d => d -> u) -> WireType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WireType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WireType -> m WireType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WireType -> m WireType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WireType -> m WireType #

Num WireType Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Ord WireType Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Read WireType Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Show WireType Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

data FieldId Source #

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).

Instances

Instances details
Bounded FieldId Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Enum FieldId Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Eq FieldId Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Methods

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

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

Data FieldId Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldId -> c FieldId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FieldId #

toConstr :: FieldId -> Constr #

dataTypeOf :: FieldId -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FieldId) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FieldId) #

gmapT :: (forall b. Data b => b -> b) -> FieldId -> FieldId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldId -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldId -> r #

gmapQ :: (forall d. Data d => d -> u) -> FieldId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldId -> m FieldId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldId -> m FieldId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldId -> m FieldId #

Num FieldId Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Ord FieldId Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Read FieldId Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Show FieldId Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Ix FieldId Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

data WireTag Source #

WireTag is the 32 bit value with the upper 29 bits being the FieldId and the lower 3 bits being the WireType

Instances

Instances details
Bounded WireTag Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Enum WireTag Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Eq WireTag Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Methods

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

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

Data WireTag Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WireTag -> c WireTag #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WireTag #

toConstr :: WireTag -> Constr #

dataTypeOf :: WireTag -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c WireTag) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WireTag) #

gmapT :: (forall b. Data b => b -> b) -> WireTag -> WireTag #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WireTag -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WireTag -> r #

gmapQ :: (forall d. Data d => d -> u) -> WireTag -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WireTag -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WireTag -> m WireTag #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WireTag -> m WireTag #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WireTag -> m WireTag #

Num WireTag Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Ord WireTag Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Read WireTag Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Show WireTag Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Bits WireTag Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

newtype Utf8 Source #

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

Instances details
Eq Utf8 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Methods

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

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

Data Utf8 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Utf8 -> c Utf8 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Utf8 #

toConstr :: Utf8 -> Constr #

dataTypeOf :: Utf8 -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Utf8) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Utf8) #

gmapT :: (forall b. Data b => b -> b) -> Utf8 -> Utf8 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Utf8 -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Utf8 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Utf8 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Utf8 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Utf8 -> m Utf8 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Utf8 -> m Utf8 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Utf8 -> m Utf8 #

Ord Utf8 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Methods

compare :: Utf8 -> Utf8 -> Ordering #

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

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

(>) :: Utf8 -> Utf8 -> Bool #

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

max :: Utf8 -> Utf8 -> Utf8 #

min :: Utf8 -> Utf8 -> Utf8 #

Read Utf8 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Show Utf8 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Methods

showsPrec :: Int -> Utf8 -> ShowS #

show :: Utf8 -> String #

showList :: [Utf8] -> ShowS #

IsString Utf8 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Methods

fromString :: String -> Utf8 #

Semigroup Utf8 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Methods

(<>) :: Utf8 -> Utf8 -> Utf8 #

sconcat :: NonEmpty Utf8 -> Utf8 #

stimes :: Integral b => b -> Utf8 -> Utf8 #

Monoid Utf8 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Methods

mempty :: Utf8 #

mappend :: Utf8 -> Utf8 -> Utf8 #

mconcat :: [Utf8] -> Utf8 #

ToJSON Utf8 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

FromJSON Utf8 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Default Utf8 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Mergeable Utf8 Source # 
Instance details

Defined in Text.ProtocolBuffers.Basic

Dotted Utf8 Source # 
Instance details

Defined in Text.ProtocolBuffers.Identifiers

TextType Utf8 Source # 
Instance details

Defined in Text.ProtocolBuffers.TextMessage

Methods

tellT :: String -> Utf8 -> Output Source #

getT :: Stream s Identity Char => String -> Parsec s () Utf8 Source #

Wire Utf8 Source # 
Instance details

Defined in Text.ProtocolBuffers.WireMessage

GPB Utf8 Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

MessageAPI msg (msg -> Utf8) Utf8 Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

Methods

getVal :: msg -> (msg -> Utf8) -> Utf8 Source #

isSet :: msg -> (msg -> Utf8) -> Bool Source #

Mangle (FIName Utf8) (PFName String) Source # 
Instance details

Defined in Text.ProtocolBuffers.Identifiers

Mangle (FIName Utf8) (PMName String) Source # 
Instance details

Defined in Text.ProtocolBuffers.Identifiers

Mangle (DIName Utf8) (PFName String) Source # 
Instance details

Defined in Text.ProtocolBuffers.Identifiers

Mangle (DIName Utf8) (PMName String) Source # 
Instance details

Defined in Text.ProtocolBuffers.Identifiers

Mangle (IName Utf8) (FName String) Source # 
Instance details

Defined in Text.ProtocolBuffers.Identifiers

Mangle (IName Utf8) (MName String) Source # 
Instance details

Defined in Text.ProtocolBuffers.Identifiers

class MessageAPI msg a b | msg a -> b where Source #

Minimal complete definition

getVal

Methods

getVal :: msg -> a -> b Source #

Access data in a message. The first argument is always the message. The second argument can be one of 4 categories.

  • The field name of a required field acts a simple retrieval of the data from the message.
  • The field name of an optional field will retreive the data if it is set or lookup the default value if it is not set.
  • The field name of a repeated field always retrieves the (possibly empty) Seq of values.
  • A Key for an optional or repeated value will act as the field name does above, but if there is a type mismatch or parse error it will use the defaultValue for optional types and an empty sequence for repeated types.

isSet :: msg -> a -> Bool Source #

Check whether data is present in the message.

  • Required fields always return True.
  • Optional fields return whether a value is present.
  • Repeated field return False if there are no values, otherwise they return True.
  • Keys return as optional or repeated, but checks only if the field # is present. This assumes that there are no collisions where more that one key refers to the same field number of this message type.

Instances

Instances details
MessageAPI msg (msg -> Word64) Word64 Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

Methods

getVal :: msg -> (msg -> Word64) -> Word64 Source #

isSet :: msg -> (msg -> Word64) -> Bool Source #

MessageAPI msg (msg -> Word32) Word32 Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

Methods

getVal :: msg -> (msg -> Word32) -> Word32 Source #

isSet :: msg -> (msg -> Word32) -> Bool Source #

MessageAPI msg (msg -> Int64) Int64 Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

Methods

getVal :: msg -> (msg -> Int64) -> Int64 Source #

isSet :: msg -> (msg -> Int64) -> Bool Source #

MessageAPI msg (msg -> Int32) Int32 Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

Methods

getVal :: msg -> (msg -> Int32) -> Int32 Source #

isSet :: msg -> (msg -> Int32) -> Bool Source #

MessageAPI msg (msg -> Float) Float Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

Methods

getVal :: msg -> (msg -> Float) -> Float Source #

isSet :: msg -> (msg -> Float) -> Bool Source #

MessageAPI msg (msg -> Double) Double Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

Methods

getVal :: msg -> (msg -> Double) -> Double Source #

isSet :: msg -> (msg -> Double) -> Bool Source #

MessageAPI msg (msg -> Utf8) Utf8 Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

Methods

getVal :: msg -> (msg -> Utf8) -> Utf8 Source #

isSet :: msg -> (msg -> Utf8) -> Bool Source #

MessageAPI msg (msg -> ByteString) ByteString Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

Methods

getVal :: msg -> (msg -> ByteString) -> ByteString Source #

isSet :: msg -> (msg -> ByteString) -> Bool Source #

(Default msg, Default a) => MessageAPI msg (msg -> Maybe a) a Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

Methods

getVal :: msg -> (msg -> Maybe a) -> a Source #

isSet :: msg -> (msg -> Maybe a) -> Bool Source #

MessageAPI msg (msg -> Seq a) (Seq a) Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

Methods

getVal :: msg -> (msg -> Seq a) -> Seq a Source #

isSet :: msg -> (msg -> Seq a) -> Bool Source #

Default v => MessageAPI msg (Key Maybe msg v) v Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

Methods

getVal :: msg -> Key Maybe msg v -> v Source #

isSet :: msg -> Key Maybe msg v -> Bool Source #

Default v => MessageAPI msg (Key Seq msg v) (Seq v) Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

Methods

getVal :: msg -> Key Seq msg v -> Seq v Source #

isSet :: msg -> Key Seq msg v -> Bool Source #

class ExtKey c where Source #

The ExtKey class has three functions for user of the API: putExt, getExt, and clearExt. The wireGetKey is used in generated code.

There are two instances of this class, Maybe for optional message fields and Seq for repeated message fields. This class allows for uniform treatment of these two kinds of extension fields.

Minimal complete definition

putExt, getExt, clearExt, wireGetKey

Methods

putExt :: Key c msg v -> c v -> msg -> msg Source #

Change or clear the value of a key in a message. Passing Nothing with an optional key or an empty Seq with a repeated key clears the value. This function thus maintains the invariant that having a field number in the ExtField map means that the field is set and not empty.

This should be only way to set the contents of a extension field.

getExt :: Key c msg v -> msg -> Either String (c v) Source #

Access the key in the message. Optional have type (Key Maybe msg v) and return type (Maybe v) while repeated fields have type (Key Seq msg v) and return type (Seq v).

There are a few sources of errors with the lookup of the key:

  • It may find unparsed bytes from loading the message. getExt will attempt to parse the bytes as the key's value type, and may fail. The parsing is done with the parseWireExt method (which is not exported to user API).
  • The wrong optional-key versus repeated-key type is a failure
  • The wrong type of the value might be found in the map and
  • cause a failure

The failures above should only happen if two different keys are used with the same field number.

clearExt :: Key c msg v -> msg -> msg Source #

Instances

Instances details
ExtKey Maybe Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

Methods

putExt :: Key Maybe msg v -> Maybe v -> msg -> msg Source #

getExt :: Key Maybe msg v -> msg -> Either String (Maybe v) Source #

clearExt :: Key Maybe msg v -> msg -> msg Source #

wireGetKey :: Key Maybe msg v -> msg -> Get msg Source #

ExtKey Seq Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

Methods

putExt :: Key Seq msg v -> Seq v -> msg -> msg Source #

getExt :: Key Seq msg v -> msg -> Either String (Seq v) Source #

clearExt :: Key Seq msg v -> msg -> msg Source #

wireGetKey :: Key Seq msg v -> msg -> Get msg Source #

ExtKey PackedSeq Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

Methods

putExt :: Key PackedSeq msg v -> PackedSeq v -> msg -> msg Source #

getExt :: Key PackedSeq msg v -> msg -> Either String (PackedSeq v) Source #

clearExt :: Key PackedSeq msg v -> msg -> msg Source #

wireGetKey :: Key PackedSeq msg v -> msg -> Get msg Source #

data Key c msg v Source #

The Key data type is used with the ExtKey class to put, get, and clear external fields of messages. The Key can also be used with the MessagesAPI to get a possibly default value and to check whether a key has been set in a message.

The Key type (opaque to the user) has a phantom type of Maybe or Seq that corresponds to Optional or Repeated fields. And a second phantom type that matches the message type it must be used with. The third type parameter corresponds to the Haskell value type.

The Key is a GADT that puts all the needed class instances into scope. The actual content is the FieldId ( numeric key), the FieldType (for sanity checks), and Maybe v (a non-standard default value).

When code is generated all of the known keys are taken into account in the deserialization from the wire. Unknown extension fields are read as a collection of raw byte sequences. If a key is then presented it will be used to parse the bytes.

There is no guarantee for what happens if two Keys disagree about the type of a field; in particular there may be undefined values and runtime errors. The data constructor for Key has to be exported to the generated code, but is not exposed to the user by Text.ProtocolBuffers.

Instances

Instances details
Default v => MessageAPI msg (Key Maybe msg v) v Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

Methods

getVal :: msg -> Key Maybe msg v -> v Source #

isSet :: msg -> Key Maybe msg v -> Bool Source #

Default v => MessageAPI msg (Key Seq msg v) (Seq v) Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

Methods

getVal :: msg -> Key Seq msg v -> Seq v Source #

isSet :: msg -> Key Seq msg v -> Bool Source #

(Typeable c, ExtendMessage msg, GPB v) => Show (Key c msg v) Source # 
Instance details

Defined in Text.ProtocolBuffers.Extensions

Methods

showsPrec :: Int -> Key c msg v -> ShowS #

show :: Key c msg v -> String #

showList :: [Key c msg v] -> ShowS #

getKeyFieldId :: Key c msg v -> FieldId Source #

This allows reflection, in this case it gives the numerical FieldId of the key, from 1 to 2^29-1 (excluding 19,000 through 19,999).

getKeyFieldType :: Key c msg v -> FieldType Source #

This allows reflection, in this case it gives the FieldType enumeration value (1 to 18) of the Text.DescriptorProtos.FieldDescriptorProto.Type of the field.

getKeyDefaultValue :: Key c msg v -> v Source #

This will return the default value for a given Key, which is set in the '.proto' file, or if unset it is the defaultValue of that type.

class ReflectDescriptor m where Source #

Minimal complete definition

reflectDescriptorInfo

Methods

getMessageInfo :: m -> GetMessageInfo Source #

This is obtained via read on the stored show output of the DescriptorInfo in the module file. It is used in getting messages from the wire.

Must not inspect argument

reflectDescriptorInfo Source #

Arguments

:: m 
-> DescriptorInfo

Must not inspect argument

class ReflectEnum e where Source #

Minimal complete definition

reflectEnum, reflectEnumInfo

Methods

reflectEnum :: EnumInfoApp e Source #

reflectEnumInfo Source #

Arguments

:: e 
-> EnumInfo

Must not inspect argument

parentOfEnum Source #

Arguments

:: e 
-> Maybe DescriptorInfo

Must not inspect argument

data EnumInfo Source #

Constructors

EnumInfo 

Fields

Instances

Instances details
Eq EnumInfo Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

Data EnumInfo Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EnumInfo -> c EnumInfo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EnumInfo #

toConstr :: EnumInfo -> Constr #

dataTypeOf :: EnumInfo -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EnumInfo) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EnumInfo) #

gmapT :: (forall b. Data b => b -> b) -> EnumInfo -> EnumInfo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EnumInfo -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EnumInfo -> r #

gmapQ :: (forall d. Data d => d -> u) -> EnumInfo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EnumInfo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EnumInfo -> m EnumInfo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EnumInfo -> m EnumInfo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EnumInfo -> m EnumInfo #

Ord EnumInfo Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

Read EnumInfo Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

Show EnumInfo Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

data HsDefault Source #

HsDefault stores the parsed default from the proto file in a form that will make a nice literal in the Language.Haskell.Exts.Syntax code generation by hprotoc.

Note that Utf8 labeled byte sequences have been stripped to just ByteString here as this is sufficient for code generation.

On 25 August 2010 20:12, George van den Driessche [email protected] sent Chris Kuklewicz a patch to MakeReflections.parseDefEnum to ensure that HsDef'Enum holds the mangled form of the name.

Instances

Instances details
Eq HsDefault Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

Data HsDefault Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsDefault -> c HsDefault #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsDefault #

toConstr :: HsDefault -> Constr #

dataTypeOf :: HsDefault -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsDefault) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsDefault) #

gmapT :: (forall b. Data b => b -> b) -> HsDefault -> HsDefault #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDefault -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDefault -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsDefault -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDefault -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDefault -> m HsDefault #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDefault -> m HsDefault #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDefault -> m HsDefault #

Ord HsDefault Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

Read HsDefault Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

Show HsDefault Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

data FieldInfo Source #

Constructors

FieldInfo 

Fields

Instances

Instances details
Eq FieldInfo Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

Data FieldInfo Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldInfo -> c FieldInfo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FieldInfo #

toConstr :: FieldInfo -> Constr #

dataTypeOf :: FieldInfo -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FieldInfo) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FieldInfo) #

gmapT :: (forall b. Data b => b -> b) -> FieldInfo -> FieldInfo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldInfo -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldInfo -> r #

gmapQ :: (forall d. Data d => d -> u) -> FieldInfo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldInfo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldInfo -> m FieldInfo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldInfo -> m FieldInfo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldInfo -> m FieldInfo #

Ord FieldInfo Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

Read FieldInfo Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

Show FieldInfo Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

data DescriptorInfo Source #

Instances

Instances details
Eq DescriptorInfo Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

Data DescriptorInfo Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DescriptorInfo -> c DescriptorInfo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DescriptorInfo #

toConstr :: DescriptorInfo -> Constr #

dataTypeOf :: DescriptorInfo -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DescriptorInfo) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DescriptorInfo) #

gmapT :: (forall b. Data b => b -> b) -> DescriptorInfo -> DescriptorInfo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DescriptorInfo -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DescriptorInfo -> r #

gmapQ :: (forall d. Data d => d -> u) -> DescriptorInfo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DescriptorInfo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DescriptorInfo -> m DescriptorInfo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DescriptorInfo -> m DescriptorInfo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DescriptorInfo -> m DescriptorInfo #

Ord DescriptorInfo Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

Read DescriptorInfo Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

Show DescriptorInfo Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

data ProtoInfo Source #

Constructors

ProtoInfo 

Fields

Instances

Instances details
Eq ProtoInfo Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

Data ProtoInfo Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ProtoInfo -> c ProtoInfo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ProtoInfo #

toConstr :: ProtoInfo -> Constr #

dataTypeOf :: ProtoInfo -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ProtoInfo) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProtoInfo) #

gmapT :: (forall b. Data b => b -> b) -> ProtoInfo -> ProtoInfo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ProtoInfo -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ProtoInfo -> r #

gmapQ :: (forall d. Data d => d -> u) -> ProtoInfo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ProtoInfo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ProtoInfo -> m ProtoInfo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ProtoInfo -> m ProtoInfo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ProtoInfo -> m ProtoInfo #

Ord ProtoInfo Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

Read ProtoInfo Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

Show ProtoInfo Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

data ProtoName Source #

This is fully qualified name data type for code generation. The haskellPrefix was possibly specified on the hprotoc command line. The parentModule is a combination of the module prefix from the '.proto' file and any nested levels of definition.

The name components are likely to have been mangled to ensure the baseName started with an uppercase letter, in [A..Z] .

Constructors

ProtoName 

Fields

Instances

Instances details
Eq ProtoName Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

Data ProtoName Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ProtoName -> c ProtoName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ProtoName #

toConstr :: ProtoName -> Constr #

dataTypeOf :: ProtoName -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ProtoName) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProtoName) #

gmapT :: (forall b. Data b => b -> b) -> ProtoName -> ProtoName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ProtoName -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ProtoName -> r #

gmapQ :: (forall d. Data d => d -> u) -> ProtoName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ProtoName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ProtoName -> m ProtoName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ProtoName -> m ProtoName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ProtoName -> m ProtoName #

Ord ProtoName Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

Read ProtoName Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

Show ProtoName Source # 
Instance details

Defined in Text.ProtocolBuffers.Reflections

makePNF :: ByteString -> [String] -> [String] -> String -> ProtoName Source #

makePNF is used by the generated code to create a ProtoName with less newtype noise.

messagePutText :: TextMsg a => a -> String Source #

This writes message as text-format protobuf to String

messageGetText :: (TextMsg a, Stream s Identity Char) => s -> Either String a Source #

This reads message as text-format protobuf from any Parsec-compatible source. Input must be completely consumed.

runPut :: Put -> ByteString #

Run the Put monad with a serialiser

type Put = PutM () #

Put merely lifts Builder into a Writer monad, applied to ().

data Get a Source #

Instances

Instances details
Monad Get Source # 
Instance details

Defined in Text.ProtocolBuffers.Get

Methods

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

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

return :: a -> Get a #

Functor Get Source # 
Instance details

Defined in Text.ProtocolBuffers.Get

Methods

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

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

MonadFail Get Source # 
Instance details

Defined in Text.ProtocolBuffers.Get

Methods

fail :: String -> Get a #

Applicative Get Source # 
Instance details

Defined in Text.ProtocolBuffers.Get

Methods

pure :: a -> Get a #

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

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

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

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

Alternative Get Source # 
Instance details

Defined in Text.ProtocolBuffers.Get

Methods

empty :: Get a #

(<|>) :: Get a -> Get a -> Get a #

some :: Get a -> Get [a] #

many :: Get a -> Get [a] #

MonadPlus Get Source # 
Instance details

Defined in Text.ProtocolBuffers.Get

Methods

mzero :: Get a #

mplus :: Get a -> Get a -> Get a #

MonadError String Get Source # 
Instance details

Defined in Text.ProtocolBuffers.Get

Methods

throwError :: String -> Get a #

catchError :: Get a -> (String -> Get a) -> Get a #

runGet :: Get a -> ByteString -> Result a Source #

runGet is the simple executor

class Wire b Source #

The Wire class is for internal use, and may change. If there is a mis-match between the FieldType and the type of b then you will get a failure at runtime.

Users should stick to the message functions defined in Text.ProtocolBuffers.WireMessage and exported to use user by Text.ProtocolBuffers. These are less likely to change.

Minimal complete definition

wireGet, wireSize, (wirePut | wirePutWithSize)

Instances

Instances details
Wire Bool Source # 
Instance details

Defined in Text.ProtocolBuffers.WireMessage

Wire Double Source # 
Instance details

Defined in Text.ProtocolBuffers.WireMessage

Wire Float Source # 
Instance details

Defined in Text.ProtocolBuffers.WireMessage

Wire Int Source # 
Instance details

Defined in Text.ProtocolBuffers.WireMessage

Wire Int32 Source # 
Instance details

Defined in Text.ProtocolBuffers.WireMessage

Wire Int64 Source # 
Instance details

Defined in Text.ProtocolBuffers.WireMessage

Wire Word32 Source # 
Instance details

Defined in Text.ProtocolBuffers.WireMessage

Wire Word64 Source # 
Instance details

Defined in Text.ProtocolBuffers.WireMessage

Wire ByteString Source # 
Instance details

Defined in Text.ProtocolBuffers.WireMessage

Wire Utf8 Source # 
Instance details

Defined in Text.ProtocolBuffers.WireMessage

messageSize :: (ReflectDescriptor msg, Wire msg) => msg -> WireSize Source #

This computes the size of the message's fields with tags on the wire with no initial tag or length (in bytes). This is also the length of the message as placed between group start and stop tags.

messageWithLengthSize :: (ReflectDescriptor msg, Wire msg) => msg -> WireSize Source #

This computes the size of the message fields as in messageSize and add the length of the encoded size to the total. Thus this is the the length of the message including the encoded length header, but without any leading tag.

messageAsFieldSize :: (ReflectDescriptor msg, Wire msg) => FieldId -> msg -> WireSize Source #

This computes the size of the messageWithLengthSize and then adds the length an initial tag with the given FieldId.

messagePut :: (ReflectDescriptor msg, Wire msg) => msg -> ByteString Source #

This is runPut applied to messagePutM. It result in a ByteString with a length of messageSize bytes.

messageWithLengthPut :: (ReflectDescriptor msg, Wire msg) => msg -> ByteString Source #

This is runPut applied to messageWithLengthPutM. It results in a ByteString with a length of messageWithLengthSize bytes.

messagePutM :: (ReflectDescriptor msg, Wire msg) => msg -> Put Source #

This writes just the message's fields with tags to the wire. This Put monad can be composed and eventually executed with runPut.

This is actually wirePut 10 msg

messageWithLengthPutM :: (ReflectDescriptor msg, Wire msg) => msg -> Put Source #

This writes the encoded length of the message's fields and then the message's fields with tags to the wire. This Put monad can be composed and eventually executed with runPut.

This is actually wirePut 11 msg

messageAsFieldPutM :: (ReflectDescriptor msg, Wire msg) => FieldId -> msg -> Put Source #

This writes an encoded wire tag with the given FieldId and then the encoded length of the message's fields and then the message's fields with tags to the wire. This Put monad can be composed and eventually executed with runPut.

messageGet :: (ReflectDescriptor msg, Wire msg) => ByteString -> Either String (msg, ByteString) Source #

This consumes the ByteString to decode a message. It assumes the ByteString is merely a sequence of the tagged fields of the message, and consumes until a group stop tag is detected or the entire input is consumed. Any ByteString past the end of the stop tag is returned as well.

This is runGetOnLazy applied to messageGetM.

messageWithLengthGet :: (ReflectDescriptor msg, Wire msg) => ByteString -> Either String (msg, ByteString) Source #

This runGetOnLazy applied to messageWithLengthGetM.

This first reads the encoded length of the message and will then succeed when it has consumed precisely this many additional bytes. The ByteString after this point will be returned.

messageGetM :: (ReflectDescriptor msg, Wire msg) => Get msg Source #

This reads the tagged message fields until the stop tag or the end of input is reached.

This is actually wireGet 10 msg

messageWithLengthGetM :: (ReflectDescriptor msg, Wire msg) => Get msg Source #

This reads the encoded message length and then the message.

This is actually wireGet 11 msg

messageAsFieldGetM :: (ReflectDescriptor msg, Wire msg) => Get (FieldId, msg) Source #

This reads a wire tag (must be of type '2') to get the FieldId. Then the encoded message length is read, followed by the message itself. Both the FieldId and the message are returned.

This allows for incremental reading and processing.

runGetOnLazy :: Get r -> ByteString -> Either String (r, ByteString) Source #

This is like runGet, without the ability to pass in more input beyond the initial ByteString. Thus the ByteString argument is taken to be the entire input. To be able to incrementally feed in more input you should use runGet and respond to Partial differently.