protobuf-0.2.1.2: Google Protocol Buffers via GHC.Generics

Safe HaskellNone
LanguageHaskell2010

Data.ProtocolBuffers.Internal

Synopsis

Documentation

type Tag = Word32 Source #

Field identifiers

data WireField Source #

A representation of the wire format as described in https://developers.google.com/protocol-buffers/docs/encoding#structure

Constructors

VarintField !Tag !Word64

For: int32, int64, uint32, uint64, sint32, sint64, bool, enum

Fixed64Field !Tag !Word64

For: fixed64, sfixed64, double

DelimitedField !Tag !ByteString

For: string, bytes, embedded messages, packed repeated fields

StartField !Tag

For: groups (deprecated)

EndField !Tag

For: groups (deprecated)

Fixed32Field !Tag !Word32

For: fixed32, sfixed32, float

class EncodeWire a where Source #

Minimal complete definition

encodeWire

Methods

encodeWire :: Tag -> a -> Put Source #

Instances

EncodeWire Bool Source # 

Methods

encodeWire :: Tag -> Bool -> Put Source #

EncodeWire Double Source # 

Methods

encodeWire :: Tag -> Double -> Put Source #

EncodeWire Float Source # 

Methods

encodeWire :: Tag -> Float -> Put Source #

EncodeWire Int32 Source # 

Methods

encodeWire :: Tag -> Int32 -> Put Source #

EncodeWire Int64 Source # 

Methods

encodeWire :: Tag -> Int64 -> Put Source #

EncodeWire Word32 Source # 

Methods

encodeWire :: Tag -> Word32 -> Put Source #

EncodeWire Word64 Source # 

Methods

encodeWire :: Tag -> Word64 -> Put Source #

EncodeWire String Source # 

Methods

encodeWire :: Tag -> String -> Put Source #

EncodeWire ByteString Source # 
EncodeWire Text Source # 

Methods

encodeWire :: Tag -> Text -> Put Source #

EncodeWire WireField Source # 
EncodeWire a => EncodeWire [Value a] Source # 

Methods

encodeWire :: Tag -> [Value a] -> Put Source #

EncodeWire a => EncodeWire (Maybe (Value a)) Source # 

Methods

encodeWire :: Tag -> Maybe (Value a) -> Put Source #

(Foldable f, Enum a) => EncodeWire (f (Enumeration a)) Source # 

Methods

encodeWire :: Tag -> f (Enumeration a) -> Put Source #

(Foldable f, Encode m) => EncodeWire (f (Message m)) Source # 

Methods

encodeWire :: Tag -> f (Message m) -> Put Source #

EncodeWire a => EncodeWire (Last (Value a)) Source # 

Methods

encodeWire :: Tag -> Last (Value a) -> Put Source #

EncodeWire (Fixed Int32) Source # 

Methods

encodeWire :: Tag -> Fixed Int32 -> Put Source #

EncodeWire (Fixed Int64) Source # 

Methods

encodeWire :: Tag -> Fixed Int64 -> Put Source #

EncodeWire (Fixed Word32) Source # 
EncodeWire (Fixed Word64) Source # 
EncodeWire (Signed Int32) Source # 
EncodeWire (Signed Int64) Source # 
Enum a => EncodeWire (PackedList (Enumeration a)) Source # 
EncodeWire (PackedList (Value Bool)) Source # 
EncodeWire (PackedList (Value Double)) Source # 
EncodeWire (PackedList (Value Float)) Source # 
EncodeWire (PackedList (Value Int32)) Source # 
EncodeWire (PackedList (Value Int64)) Source # 
EncodeWire (PackedList (Value Word32)) Source # 
EncodeWire (PackedList (Value Word64)) Source # 
EncodeWire (PackedList (Value (Fixed Int32))) Source # 
EncodeWire (PackedList (Value (Fixed Int64))) Source # 
EncodeWire (PackedList (Value (Fixed Word32))) Source # 
EncodeWire (PackedList (Value (Fixed Word64))) Source # 
EncodeWire (PackedList (Value (Signed Int32))) Source # 
EncodeWire (PackedList (Value (Signed Int64))) Source # 
EncodeWire a => EncodeWire (Always (Value a)) Source # 

Methods

encodeWire :: Tag -> Always (Value a) -> Put Source #

EncodeWire a => EncodeWire (Value a) Source # 

Methods

encodeWire :: Tag -> Value a -> Put Source #

class DecodeWire a where Source #

Minimal complete definition

decodeWire

Instances

DecodeWire Bool Source # 
DecodeWire Double Source # 
DecodeWire Float Source # 
DecodeWire Int32 Source # 
DecodeWire Int64 Source # 
DecodeWire Word32 Source # 
DecodeWire Word64 Source # 
DecodeWire String Source # 
DecodeWire ByteString Source # 
DecodeWire Text Source # 
DecodeWire WireField Source # 
Enum a => DecodeWire (Maybe (Enumeration a)) Source # 
DecodeWire a => DecodeWire (Maybe (Value a)) Source # 
DecodeWire a => DecodeWire (Last (Value a)) Source # 
DecodeWire (Fixed Int32) Source # 
DecodeWire (Fixed Int64) Source # 
DecodeWire (Fixed Word32) Source # 
DecodeWire (Fixed Word64) Source # 
DecodeWire (Signed Int32) Source # 
DecodeWire (Signed Int64) Source # 
Enum a => DecodeWire (PackedList (Enumeration a)) Source # 
DecodeWire (PackedList (Value Bool)) Source # 
DecodeWire (PackedList (Value Double)) Source # 
DecodeWire (PackedList (Value Float)) Source # 
DecodeWire (PackedList (Value Int32)) Source # 
DecodeWire (PackedList (Value Int64)) Source # 
DecodeWire (PackedList (Value Word32)) Source # 
DecodeWire (PackedList (Value Word64)) Source # 
DecodeWire (PackedList (Value (Fixed Int32))) Source # 
DecodeWire (PackedList (Value (Fixed Int64))) Source # 
DecodeWire (PackedList (Value (Fixed Word32))) Source # 
DecodeWire (PackedList (Value (Fixed Word64))) Source # 
DecodeWire (PackedList (Value (Signed Int32))) Source # 
DecodeWire (PackedList (Value (Signed Int64))) Source # 
Enum a => DecodeWire (Enumeration a) Source # 
Enum a => DecodeWire (Always (Enumeration a)) Source # 
DecodeWire a => DecodeWire (Always (Value a)) Source # 
DecodeWire a => DecodeWire (Value a) Source # 
Decode m => DecodeWire (Message m) Source # 

putVarSInt :: (Integral a, Bits a) => a -> Put Source #

This can be used on any Integral type and is needed for signed types; unsigned can use putVarUInt below. This has been changed to handle only up to 64 bit integral values (to match documentation).

putVarUInt :: (Integral a, Bits a) => a -> Put Source #

This should be used on unsigned Integral types only (not checked)

newtype Field (n :: Nat) a Source #

Fields are merely a way to hold a field tag along with its type, this shouldn't normally be referenced directly.

This provides better error messages than older versions which used Tagged

Constructors

Field 

Fields

Instances

Functor (Field n) Source # 

Methods

fmap :: (a -> b) -> Field n a -> Field n b #

(<$) :: a -> Field n b -> Field n a #

Foldable (Field n) Source # 

Methods

fold :: Monoid m => Field n m -> m #

foldMap :: Monoid m => (a -> m) -> Field n a -> m #

foldr :: (a -> b -> b) -> b -> Field n a -> b #

foldr' :: (a -> b -> b) -> b -> Field n a -> b #

foldl :: (b -> a -> b) -> b -> Field n a -> b #

foldl' :: (b -> a -> b) -> b -> Field n a -> b #

foldr1 :: (a -> a -> a) -> Field n a -> a #

foldl1 :: (a -> a -> a) -> Field n a -> a #

toList :: Field n a -> [a] #

null :: Field n a -> Bool #

length :: Field n a -> Int #

elem :: Eq a => a -> Field n a -> Bool #

maximum :: Ord a => Field n a -> a #

minimum :: Ord a => Field n a -> a #

sum :: Num a => Field n a -> a #

product :: Num a => Field n a -> a #

Traversable (Field n) Source # 

Methods

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

sequenceA :: Applicative f => Field n (f a) -> f (Field n a) #

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

sequence :: Monad m => Field n (m a) -> m (Field n a) #

Bounded a => Bounded (Field n a) Source # 

Methods

minBound :: Field n a #

maxBound :: Field n a #

Enum a => Enum (Field n a) Source # 

Methods

succ :: Field n a -> Field n a #

pred :: Field n a -> Field n a #

toEnum :: Int -> Field n a #

fromEnum :: Field n a -> Int #

enumFrom :: Field n a -> [Field n a] #

enumFromThen :: Field n a -> Field n a -> [Field n a] #

enumFromTo :: Field n a -> Field n a -> [Field n a] #

enumFromThenTo :: Field n a -> Field n a -> Field n a -> [Field n a] #

Eq a => Eq (Field n a) Source # 

Methods

(==) :: Field n a -> Field n a -> Bool #

(/=) :: Field n a -> Field n a -> Bool #

Ord a => Ord (Field n a) Source # 

Methods

compare :: Field n a -> Field n a -> Ordering #

(<) :: Field n a -> Field n a -> Bool #

(<=) :: Field n a -> Field n a -> Bool #

(>) :: Field n a -> Field n a -> Bool #

(>=) :: Field n a -> Field n a -> Bool #

max :: Field n a -> Field n a -> Field n a #

min :: Field n a -> Field n a -> Field n a #

Show a => Show (Field n a) Source # 

Methods

showsPrec :: Int -> Field n a -> ShowS #

show :: Field n a -> String #

showList :: [Field n a] -> ShowS #

Semigroup a => Semigroup (Field n a) Source # 

Methods

(<>) :: Field n a -> Field n a -> Field n a #

sconcat :: NonEmpty (Field n a) -> Field n a #

stimes :: Integral b => b -> Field n a -> Field n a #

Monoid a => Monoid (Field n a) Source # 

Methods

mempty :: Field n a #

mappend :: Field n a -> Field n a -> Field n a #

mconcat :: [Field n a] -> Field n a #

NFData a => NFData (Field n a) Source # 

Methods

rnf :: Field n a -> () #

HasField (Field n (PackedField (PackedList (Enumeration a)))) Source #

Iso: FieldType (Packed n (Enumeration a)) = [a]

HasField (Field n (PackedField (PackedList (Value a)))) Source #

Iso: FieldType (Packed n (Value a)) = [a]

HasField (Field n (RepeatedField [Enumeration a])) Source #

Iso: FieldType (Repeated n (Enumeration a)) = [a]

HasField (Field n (RepeatedField [Value a])) Source #

Iso: FieldType (Repeated n (Value a)) = [a]

HasField (Field n (OptionalField (Last (Enumeration a)))) Source #

Iso: FieldType (Optional n (Enumeration a)) = Maybe a

HasField (Field n (OptionalField (Last (Value a)))) Source #

Iso: FieldType (Optional n (Value a)) = Maybe a

HasField (Field n (RequiredField (Always (Enumeration a)))) Source #

Iso: FieldType (Required n (Enumeration a)) = a

HasField (Field n (RequiredField (Always (Value a)))) Source #

Iso: FieldType (Required n (Value a)) = a

HasField (Field n (RepeatedField [Message a])) Source #

Iso: FieldType (Repeated n (Message a)) = [a]

HasField (Field n (OptionalField (Maybe (Message a)))) Source #

Iso: FieldType (Optional n (Message a)) = Maybe a

HasField (Field n (RequiredField (Always (Message a)))) Source #

Iso: FieldType (Required n (Message a)) = a

(EncodeWire a, KnownNat n, Foldable f) => GEncode (K1 * i (Field n (f a))) Source # 

Methods

gencode :: K1 * i (Field n (f a)) a -> Put

(DecodeWire (PackedList a), KnownNat n) => GDecode (K1 * i (Packed n a)) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 * i (Packed n a) a)

(DecodeWire a, KnownNat n) => GDecode (K1 * i (Field n (RequiredField (Always (Value a))))) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 * i (Field n (RequiredField (Always (Value a)))) a)

(DecodeWire a, KnownNat n) => GDecode (K1 * i (Repeated n a)) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 * i (Repeated n a) a)

(Enum a, KnownNat n) => GDecode (K1 * i (Field n (OptionalField (Last (Enumeration a))))) Source # 
(Enum a, KnownNat n) => GDecode (K1 * i (Field n (RequiredField (Always (Enumeration a))))) Source # 
(DecodeWire a, KnownNat n) => GDecode (K1 * i (Field n (OptionalField (Last (Value a))))) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 * i (Field n (OptionalField (Last (Value a)))) a)

(Decode a, Monoid (Message a), KnownNat n) => GDecode (K1 * i (Field n (OptionalField (Maybe (Message a))))) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 * i (Field n (OptionalField (Maybe (Message a)))) a)

(Decode a, Monoid (Message a), KnownNat n) => GDecode (K1 * i (Field n (RequiredField (Always (Message a))))) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 * i (Field n (RequiredField (Always (Message a)))) a)

type FieldType (Field n (RepeatedField [Value a])) Source # 
type FieldType (Field n (RepeatedField [Value a])) = [a]
type FieldType (Field n (OptionalField (Last (Value a)))) Source # 
type FieldType (Field n (RequiredField (Always (Value a)))) Source # 
type FieldType (Field n (RepeatedField [Enumeration a])) Source # 
type FieldType (Field n (OptionalField (Last (Enumeration a)))) Source # 
type FieldType (Field n (RequiredField (Always (Enumeration a)))) Source # 
type FieldType (Field n (PackedField (PackedList (Enumeration a)))) Source # 
type FieldType (Field n (PackedField (PackedList (Value a)))) Source # 
type FieldType (Field n (PackedField (PackedList (Value a)))) = [a]
type FieldType (Field n (RepeatedField [Message a])) Source # 
type FieldType (Field n (RepeatedField [Message a])) = [a]
type FieldType (Field n (OptionalField (Maybe (Message a)))) Source # 
type FieldType (Field n (RequiredField (Always (Message a)))) Source # 

newtype Value a Source #

Value selects the normal/typical way for encoding scalar (primitive) values.

Constructors

Value 

Fields

Instances

Functor Value Source # 

Methods

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

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

Foldable Value Source # 

Methods

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

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

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

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

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

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

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

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

toList :: Value a -> [a] #

null :: Value a -> Bool #

length :: Value a -> Int #

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

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

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

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

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

Traversable Value Source # 

Methods

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

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

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

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

Bounded a => Bounded (Value a) Source # 

Methods

minBound :: Value a #

maxBound :: Value a #

Enum a => Enum (Value a) Source # 

Methods

succ :: Value a -> Value a #

pred :: Value a -> Value a #

toEnum :: Int -> Value a #

fromEnum :: Value a -> Int #

enumFrom :: Value a -> [Value a] #

enumFromThen :: Value a -> Value a -> [Value a] #

enumFromTo :: Value a -> Value a -> [Value a] #

enumFromThenTo :: Value a -> Value a -> Value a -> [Value a] #

Eq a => Eq (Value a) Source # 

Methods

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

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

Ord a => Ord (Value a) Source # 

Methods

compare :: Value a -> Value a -> Ordering #

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

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

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

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

max :: Value a -> Value a -> Value a #

min :: Value a -> Value a -> Value a #

Show a => Show (Value a) Source # 

Methods

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

show :: Value a -> String #

showList :: [Value a] -> ShowS #

Semigroup a => Semigroup (Value a) Source # 

Methods

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

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

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

Monoid a => Monoid (Value a) Source # 

Methods

mempty :: Value a #

mappend :: Value a -> Value a -> Value a #

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

NFData a => NFData (Value a) Source # 

Methods

rnf :: Value a -> () #

DecodeWire a => DecodeWire (Maybe (Value a)) Source # 
DecodeWire a => DecodeWire (Last (Value a)) Source # 
DecodeWire (PackedList (Value Bool)) Source # 
DecodeWire (PackedList (Value Double)) Source # 
DecodeWire (PackedList (Value Float)) Source # 
DecodeWire (PackedList (Value Int32)) Source # 
DecodeWire (PackedList (Value Int64)) Source # 
DecodeWire (PackedList (Value Word32)) Source # 
DecodeWire (PackedList (Value Word64)) Source # 
DecodeWire (PackedList (Value (Fixed Int32))) Source # 
DecodeWire (PackedList (Value (Fixed Int64))) Source # 
DecodeWire (PackedList (Value (Fixed Word32))) Source # 
DecodeWire (PackedList (Value (Fixed Word64))) Source # 
DecodeWire (PackedList (Value (Signed Int32))) Source # 
DecodeWire (PackedList (Value (Signed Int64))) Source # 
DecodeWire a => DecodeWire (Always (Value a)) Source # 
DecodeWire a => DecodeWire (Value a) Source # 
EncodeWire a => EncodeWire [Value a] Source # 

Methods

encodeWire :: Tag -> [Value a] -> Put Source #

EncodeWire a => EncodeWire (Maybe (Value a)) Source # 

Methods

encodeWire :: Tag -> Maybe (Value a) -> Put Source #

EncodeWire a => EncodeWire (Last (Value a)) Source # 

Methods

encodeWire :: Tag -> Last (Value a) -> Put Source #

EncodeWire (PackedList (Value Bool)) Source # 
EncodeWire (PackedList (Value Double)) Source # 
EncodeWire (PackedList (Value Float)) Source # 
EncodeWire (PackedList (Value Int32)) Source # 
EncodeWire (PackedList (Value Int64)) Source # 
EncodeWire (PackedList (Value Word32)) Source # 
EncodeWire (PackedList (Value Word64)) Source # 
EncodeWire (PackedList (Value (Fixed Int32))) Source # 
EncodeWire (PackedList (Value (Fixed Int64))) Source # 
EncodeWire (PackedList (Value (Fixed Word32))) Source # 
EncodeWire (PackedList (Value (Fixed Word64))) Source # 
EncodeWire (PackedList (Value (Signed Int32))) Source # 
EncodeWire (PackedList (Value (Signed Int64))) Source # 
EncodeWire a => EncodeWire (Always (Value a)) Source # 

Methods

encodeWire :: Tag -> Always (Value a) -> Put Source #

EncodeWire a => EncodeWire (Value a) Source # 

Methods

encodeWire :: Tag -> Value a -> Put Source #

HasField (Field n (PackedField (PackedList (Value a)))) Source #

Iso: FieldType (Packed n (Value a)) = [a]

HasField (Field n (RepeatedField [Value a])) Source #

Iso: FieldType (Repeated n (Value a)) = [a]

HasField (Field n (OptionalField (Last (Value a)))) Source #

Iso: FieldType (Optional n (Value a)) = Maybe a

HasField (Field n (RequiredField (Always (Value a)))) Source #

Iso: FieldType (Required n (Value a)) = a

(DecodeWire a, KnownNat n) => GDecode (K1 * i (Field n (RequiredField (Always (Value a))))) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 * i (Field n (RequiredField (Always (Value a)))) a)

(DecodeWire a, KnownNat n) => GDecode (K1 * i (Field n (OptionalField (Last (Value a))))) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 * i (Field n (OptionalField (Last (Value a)))) a)

type Required n (Value a) Source # 
type Required n (Value a) = Field n (RequiredField (Always (Value a)))
type Optional n (Value a) Source # 
type Optional n (Value a) = Field n (OptionalField (Last (Value a)))
type FieldType (Field n (RepeatedField [Value a])) Source # 
type FieldType (Field n (RepeatedField [Value a])) = [a]
type FieldType (Field n (OptionalField (Last (Value a)))) Source # 
type FieldType (Field n (RequiredField (Always (Value a)))) Source # 
type FieldType (Field n (PackedField (PackedList (Value a)))) Source # 
type FieldType (Field n (PackedField (PackedList (Value a)))) = [a]

newtype Always a Source #

To provide consistent instances for serialization a Traversable Functor is needed to make Required fields have the same shape as Optional, Repeated and Packed.

This is the Identity Functor with a Show instance.

Constructors

Always 

Fields

Instances

Functor Always Source # 

Methods

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

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

Foldable Always Source # 

Methods

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

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

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

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

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

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

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

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

toList :: Always a -> [a] #

null :: Always a -> Bool #

length :: Always a -> Int #

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

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

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

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

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

Traversable Always Source # 

Methods

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

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

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

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

Bounded a => Bounded (Always a) Source # 

Methods

minBound :: Always a #

maxBound :: Always a #

Enum a => Enum (Always a) Source # 

Methods

succ :: Always a -> Always a #

pred :: Always a -> Always a #

toEnum :: Int -> Always a #

fromEnum :: Always a -> Int #

enumFrom :: Always a -> [Always a] #

enumFromThen :: Always a -> Always a -> [Always a] #

enumFromTo :: Always a -> Always a -> [Always a] #

enumFromThenTo :: Always a -> Always a -> Always a -> [Always a] #

Eq a => Eq (Always a) Source # 

Methods

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

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

Ord a => Ord (Always a) Source # 

Methods

compare :: Always a -> Always a -> Ordering #

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

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

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

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

max :: Always a -> Always a -> Always a #

min :: Always a -> Always a -> Always a #

Show a => Show (Always a) Source # 

Methods

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

show :: Always a -> String #

showList :: [Always a] -> ShowS #

Semigroup (Always a) Source # 

Methods

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

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

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

Monoid (Always a) Source # 

Methods

mempty :: Always a #

mappend :: Always a -> Always a -> Always a #

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

NFData a => NFData (Always a) Source # 

Methods

rnf :: Always a -> () #

Enum a => DecodeWire (Always (Enumeration a)) Source # 
DecodeWire a => DecodeWire (Always (Value a)) Source # 
EncodeWire a => EncodeWire (Always (Value a)) Source # 

Methods

encodeWire :: Tag -> Always (Value a) -> Put Source #

HasField (Field n (RequiredField (Always (Enumeration a)))) Source #

Iso: FieldType (Required n (Enumeration a)) = a

HasField (Field n (RequiredField (Always (Value a)))) Source #

Iso: FieldType (Required n (Value a)) = a

HasField (Field n (RequiredField (Always (Message a)))) Source #

Iso: FieldType (Required n (Message a)) = a

(DecodeWire a, KnownNat n) => GDecode (K1 * i (Field n (RequiredField (Always (Value a))))) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 * i (Field n (RequiredField (Always (Value a)))) a)

(Enum a, KnownNat n) => GDecode (K1 * i (Field n (RequiredField (Always (Enumeration a))))) Source # 
(Decode a, Monoid (Message a), KnownNat n) => GDecode (K1 * i (Field n (RequiredField (Always (Message a))))) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 * i (Field n (RequiredField (Always (Message a)))) a)

type FieldType (Field n (RequiredField (Always (Value a)))) Source # 
type FieldType (Field n (RequiredField (Always (Enumeration a)))) Source # 
type FieldType (Field n (RequiredField (Always (Message a)))) Source # 

newtype Enumeration a Source #

Enumeration fields use fromEnum and toEnum when encoding and decoding messages.

Constructors

Enumeration 

Fields

Instances

Functor Enumeration Source # 

Methods

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

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

Foldable Enumeration Source # 

Methods

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

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

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

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

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

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

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

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

toList :: Enumeration a -> [a] #

null :: Enumeration a -> Bool #

length :: Enumeration a -> Int #

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

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

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

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

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

Traversable Enumeration Source # 

Methods

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

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

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

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

Bounded a => Bounded (Enumeration a) Source # 
Enum a => Enum (Enumeration a) Source # 
Eq a => Eq (Enumeration a) Source # 
Ord a => Ord (Enumeration a) Source # 
Show a => Show (Enumeration a) Source # 
Semigroup a => Semigroup (Enumeration a) Source # 
Monoid a => Monoid (Enumeration a) Source # 
NFData a => NFData (Enumeration a) Source # 

Methods

rnf :: Enumeration a -> () #

Enum a => DecodeWire (Maybe (Enumeration a)) Source # 
Enum a => DecodeWire (PackedList (Enumeration a)) Source # 
Enum a => DecodeWire (Enumeration a) Source # 
Enum a => DecodeWire (Always (Enumeration a)) Source # 
(Foldable f, Enum a) => EncodeWire (f (Enumeration a)) Source # 

Methods

encodeWire :: Tag -> f (Enumeration a) -> Put Source #

Enum a => EncodeWire (PackedList (Enumeration a)) Source # 
HasField (Field n (PackedField (PackedList (Enumeration a)))) Source #

Iso: FieldType (Packed n (Enumeration a)) = [a]

HasField (Field n (RepeatedField [Enumeration a])) Source #

Iso: FieldType (Repeated n (Enumeration a)) = [a]

HasField (Field n (OptionalField (Last (Enumeration a)))) Source #

Iso: FieldType (Optional n (Enumeration a)) = Maybe a

HasField (Field n (RequiredField (Always (Enumeration a)))) Source #

Iso: FieldType (Required n (Enumeration a)) = a

(Enum a, KnownNat n) => GDecode (K1 * i (Field n (OptionalField (Last (Enumeration a))))) Source # 
(Enum a, KnownNat n) => GDecode (K1 * i (Field n (RequiredField (Always (Enumeration a))))) Source # 
type Required n (Enumeration a) Source # 
type Optional n (Enumeration a) Source # 
type FieldType (Field n (RepeatedField [Enumeration a])) Source # 
type FieldType (Field n (OptionalField (Last (Enumeration a)))) Source # 
type FieldType (Field n (RequiredField (Always (Enumeration a)))) Source # 
type FieldType (Field n (PackedField (PackedList (Enumeration a)))) Source # 

newtype RequiredField a Source #

RequiredField is a newtype wrapped used to break overlapping instances for encoding and decoding values

Constructors

Required 

Fields

Instances

Functor RequiredField Source # 

Methods

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

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

Foldable RequiredField Source # 

Methods

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

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

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

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

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

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

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

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

toList :: RequiredField a -> [a] #

null :: RequiredField a -> Bool #

length :: RequiredField a -> Int #

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

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

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

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

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

Traversable RequiredField Source # 

Methods

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

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

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

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

Bounded a => Bounded (RequiredField a) Source # 
Enum a => Enum (RequiredField a) Source # 
Eq a => Eq (RequiredField a) Source # 
Ord a => Ord (RequiredField a) Source # 
Show a => Show (RequiredField a) Source # 
Semigroup a => Semigroup (RequiredField a) Source # 
Monoid a => Monoid (RequiredField a) Source # 
NFData a => NFData (RequiredField a) Source # 

Methods

rnf :: RequiredField a -> () #

HasField (Field n (RequiredField (Always (Enumeration a)))) Source #

Iso: FieldType (Required n (Enumeration a)) = a

HasField (Field n (RequiredField (Always (Value a)))) Source #

Iso: FieldType (Required n (Value a)) = a

HasField (Field n (RequiredField (Always (Message a)))) Source #

Iso: FieldType (Required n (Message a)) = a

(DecodeWire a, KnownNat n) => GDecode (K1 * i (Field n (RequiredField (Always (Value a))))) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 * i (Field n (RequiredField (Always (Value a)))) a)

(Enum a, KnownNat n) => GDecode (K1 * i (Field n (RequiredField (Always (Enumeration a))))) Source # 
(Decode a, Monoid (Message a), KnownNat n) => GDecode (K1 * i (Field n (RequiredField (Always (Message a))))) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 * i (Field n (RequiredField (Always (Message a)))) a)

type FieldType (Field n (RequiredField (Always (Value a)))) Source # 
type FieldType (Field n (RequiredField (Always (Enumeration a)))) Source # 
type FieldType (Field n (RequiredField (Always (Message a)))) Source # 

newtype OptionalField a Source #

OptionalField is a newtype wrapped used to break overlapping instances for encoding and decoding values

Constructors

Optional 

Fields

Instances

Functor OptionalField Source # 

Methods

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

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

Foldable OptionalField Source # 

Methods

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

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

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

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

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

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

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

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

toList :: OptionalField a -> [a] #

null :: OptionalField a -> Bool #

length :: OptionalField a -> Int #

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

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

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

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

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

Traversable OptionalField Source # 

Methods

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

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

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

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

Bounded a => Bounded (OptionalField a) Source # 
Enum a => Enum (OptionalField a) Source # 
Eq a => Eq (OptionalField a) Source # 
Ord a => Ord (OptionalField a) Source # 
Show a => Show (OptionalField a) Source # 
Semigroup a => Semigroup (OptionalField a) Source # 
Monoid a => Monoid (OptionalField a) Source # 
NFData a => NFData (OptionalField a) Source # 

Methods

rnf :: OptionalField a -> () #

HasField (Field n (OptionalField (Last (Enumeration a)))) Source #

Iso: FieldType (Optional n (Enumeration a)) = Maybe a

HasField (Field n (OptionalField (Last (Value a)))) Source #

Iso: FieldType (Optional n (Value a)) = Maybe a

HasField (Field n (OptionalField (Maybe (Message a)))) Source #

Iso: FieldType (Optional n (Message a)) = Maybe a

(Enum a, KnownNat n) => GDecode (K1 * i (Field n (OptionalField (Last (Enumeration a))))) Source # 
(DecodeWire a, KnownNat n) => GDecode (K1 * i (Field n (OptionalField (Last (Value a))))) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 * i (Field n (OptionalField (Last (Value a)))) a)

(Decode a, Monoid (Message a), KnownNat n) => GDecode (K1 * i (Field n (OptionalField (Maybe (Message a))))) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 * i (Field n (OptionalField (Maybe (Message a)))) a)

type FieldType (Field n (OptionalField (Last (Value a)))) Source # 
type FieldType (Field n (OptionalField (Last (Enumeration a)))) Source # 
type FieldType (Field n (OptionalField (Maybe (Message a)))) Source # 

newtype RepeatedField a Source #

RepeatedField is a newtype wrapped used to break overlapping instances for encoding and decoding values

Constructors

Repeated 

Fields

Instances

Functor RepeatedField Source # 

Methods

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

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

Foldable RepeatedField Source # 

Methods

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

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

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

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

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

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

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

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

toList :: RepeatedField a -> [a] #

null :: RepeatedField a -> Bool #

length :: RepeatedField a -> Int #

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

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

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

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

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

Traversable RepeatedField Source # 

Methods

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

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

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

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

Bounded a => Bounded (RepeatedField a) Source # 
Enum a => Enum (RepeatedField a) Source # 
Eq a => Eq (RepeatedField a) Source # 
Ord a => Ord (RepeatedField a) Source # 
Show a => Show (RepeatedField a) Source # 
Semigroup a => Semigroup (RepeatedField a) Source # 
Monoid a => Monoid (RepeatedField a) Source # 
NFData a => NFData (RepeatedField a) Source # 

Methods

rnf :: RepeatedField a -> () #

HasField (Field n (RepeatedField [Enumeration a])) Source #

Iso: FieldType (Repeated n (Enumeration a)) = [a]

HasField (Field n (RepeatedField [Value a])) Source #

Iso: FieldType (Repeated n (Value a)) = [a]

HasField (Field n (RepeatedField [Message a])) Source #

Iso: FieldType (Repeated n (Message a)) = [a]

(DecodeWire a, KnownNat n) => GDecode (K1 * i (Repeated n a)) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 * i (Repeated n a) a)

type FieldType (Field n (RepeatedField [Value a])) Source # 
type FieldType (Field n (RepeatedField [Value a])) = [a]
type FieldType (Field n (RepeatedField [Enumeration a])) Source # 
type FieldType (Field n (RepeatedField [Message a])) Source # 
type FieldType (Field n (RepeatedField [Message a])) = [a]

newtype PackedField a Source #

A Traversable Functor used to select packed sequence encoding/decoding.

Constructors

PackedField 

Fields

Instances

Functor PackedField Source # 

Methods

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

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

Foldable PackedField Source # 

Methods

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

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

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

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

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

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

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

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

toList :: PackedField a -> [a] #

null :: PackedField a -> Bool #

length :: PackedField a -> Int #

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

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

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

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

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

Traversable PackedField Source # 

Methods

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

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

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

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

Eq a => Eq (PackedField a) Source # 
Ord a => Ord (PackedField a) Source # 
Show a => Show (PackedField a) Source # 
Semigroup a => Semigroup (PackedField a) Source # 
Monoid a => Monoid (PackedField a) Source # 
NFData a => NFData (PackedField a) Source # 

Methods

rnf :: PackedField a -> () #

HasField (Field n (PackedField (PackedList (Enumeration a)))) Source #

Iso: FieldType (Packed n (Enumeration a)) = [a]

HasField (Field n (PackedField (PackedList (Value a)))) Source #

Iso: FieldType (Packed n (Value a)) = [a]

(DecodeWire (PackedList a), KnownNat n) => GDecode (K1 * i (Packed n a)) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 * i (Packed n a) a)

type FieldType (Field n (PackedField (PackedList (Enumeration a)))) Source # 
type FieldType (Field n (PackedField (PackedList (Value a)))) Source # 
type FieldType (Field n (PackedField (PackedList (Value a)))) = [a]

newtype PackedList a Source #

A list that is stored in a packed format.

Constructors

PackedList 

Fields

Instances

Functor PackedList Source # 

Methods

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

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

Foldable PackedList Source # 

Methods

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

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

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

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

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

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

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

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

toList :: PackedList a -> [a] #

null :: PackedList a -> Bool #

length :: PackedList a -> Int #

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

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

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

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

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

Traversable PackedList Source # 

Methods

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

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

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

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

Eq a => Eq (PackedList a) Source # 

Methods

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

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

Ord a => Ord (PackedList a) Source # 
Show a => Show (PackedList a) Source # 
Semigroup (PackedList a) Source # 
Monoid (PackedList a) Source # 
NFData a => NFData (PackedList a) Source # 

Methods

rnf :: PackedList a -> () #

Enum a => DecodeWire (PackedList (Enumeration a)) Source # 
DecodeWire (PackedList (Value Bool)) Source # 
DecodeWire (PackedList (Value Double)) Source # 
DecodeWire (PackedList (Value Float)) Source # 
DecodeWire (PackedList (Value Int32)) Source # 
DecodeWire (PackedList (Value Int64)) Source # 
DecodeWire (PackedList (Value Word32)) Source # 
DecodeWire (PackedList (Value Word64)) Source # 
DecodeWire (PackedList (Value (Fixed Int32))) Source # 
DecodeWire (PackedList (Value (Fixed Int64))) Source # 
DecodeWire (PackedList (Value (Fixed Word32))) Source # 
DecodeWire (PackedList (Value (Fixed Word64))) Source # 
DecodeWire (PackedList (Value (Signed Int32))) Source # 
DecodeWire (PackedList (Value (Signed Int64))) Source # 
Enum a => EncodeWire (PackedList (Enumeration a)) Source # 
EncodeWire (PackedList (Value Bool)) Source # 
EncodeWire (PackedList (Value Double)) Source # 
EncodeWire (PackedList (Value Float)) Source # 
EncodeWire (PackedList (Value Int32)) Source # 
EncodeWire (PackedList (Value Int64)) Source # 
EncodeWire (PackedList (Value Word32)) Source # 
EncodeWire (PackedList (Value Word64)) Source # 
EncodeWire (PackedList (Value (Fixed Int32))) Source # 
EncodeWire (PackedList (Value (Fixed Int64))) Source # 
EncodeWire (PackedList (Value (Fixed Word32))) Source # 
EncodeWire (PackedList (Value (Fixed Word64))) Source # 
EncodeWire (PackedList (Value (Signed Int32))) Source # 
EncodeWire (PackedList (Value (Signed Int64))) Source # 
HasField (Field n (PackedField (PackedList (Enumeration a)))) Source #

Iso: FieldType (Packed n (Enumeration a)) = [a]

HasField (Field n (PackedField (PackedList (Value a)))) Source #

Iso: FieldType (Packed n (Value a)) = [a]

(DecodeWire (PackedList a), KnownNat n) => GDecode (K1 * i (Packed n a)) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 * i (Packed n a) a)

type FieldType (Field n (PackedField (PackedList (Enumeration a)))) Source # 
type FieldType (Field n (PackedField (PackedList (Value a)))) Source # 
type FieldType (Field n (PackedField (PackedList (Value a)))) = [a]

newtype Message m Source #

The way to embed a message within another message. These embedded messages are stored as length-delimited fields.

For example:

data Inner = Inner
   { innerField :: Required '1' (Value Int64)
   } deriving (Generic, Show)

 instance Encode Inner
instance Decode Inner

 data Outer = Outer
   { outerField :: Required '1' (Message Inner)
   } deriving (Generic, Show)

 instance Encode Outer
instance Decode Outer
 

It's worth noting that Message a is a Monoid and NFData instance. The Monoid behavior models that of the Protocol Buffers documentation, effectively Last. It's done with a fairly big hammer and it isn't possible to override this behavior. This can cause some less-obvious compile errors for paramterized Message types:

data Inner = Inner{inner :: Required '2' (Value Float)} deriving (Generic, Show)
instance Encode Inner
instance Decode Inner

data Outer a = Outer{outer :: Required '3' (Message a)} deriving (Generic, Show)
instance Encode a => Encode (Outer a)
instance Decode a => Decode (Outer a)
 

This fails because Decode needs to know that the message can be merged. The resulting error implies that you may want to add a constraint to the internal GMessageMonoid class:

/tmp/tst.hs:18:10:
  Could not deduce (protobuf-0.1:GMessageMonoid (Rep a))
    arising from a use of `protobuf-0.1: Decode .$gdmdecode'
  from the context (Decode a)
    bound by the instance declaration at /tmp/tst.hs:18:10-39
  Possible fix:
    add an instance declaration for
    (protobuf-0.1:GMessageMonoid (Rep a))
  In the expression:
    (protobuf-0.1:Decode.$gdmdecode)
  In an equation for decode:
      decode = (protobuf-0.1:Decode .$gdmdecode)
  In the instance declaration for `Decode (Outer a)'

The correct fix is to add the Monoid constraint for the message:

- instance (Encode a) => Decode (Outer a)
+ instance (Monoid (Message a), Decode a) => Decode (Outer a)

Constructors

Message 

Fields

Instances

Functor Message Source # 

Methods

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

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

Foldable Message Source # 

Methods

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

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

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

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

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

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

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

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

toList :: Message a -> [a] #

null :: Message a -> Bool #

length :: Message a -> Int #

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

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

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

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

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

Traversable Message Source # 

Methods

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

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

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

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

Eq m => Eq (Message m) Source # 

Methods

(==) :: Message m -> Message m -> Bool #

(/=) :: Message m -> Message m -> Bool #

Ord m => Ord (Message m) Source # 

Methods

compare :: Message m -> Message m -> Ordering #

(<) :: Message m -> Message m -> Bool #

(<=) :: Message m -> Message m -> Bool #

(>) :: Message m -> Message m -> Bool #

(>=) :: Message m -> Message m -> Bool #

max :: Message m -> Message m -> Message m #

min :: Message m -> Message m -> Message m #

Show m => Show (Message m) Source # 

Methods

showsPrec :: Int -> Message m -> ShowS #

show :: Message m -> String #

showList :: [Message m] -> ShowS #

(Generic m, GMessageMonoid (Rep m)) => Semigroup (Message m) Source # 

Methods

(<>) :: Message m -> Message m -> Message m #

sconcat :: NonEmpty (Message m) -> Message m #

stimes :: Integral b => b -> Message m -> Message m #

(Generic m, GMessageMonoid (Rep m)) => Monoid (Message m) Source # 

Methods

mempty :: Message m #

mappend :: Message m -> Message m -> Message m #

mconcat :: [Message m] -> Message m #

(Generic m, GMessageNFData (Rep m)) => NFData (Message m) Source # 

Methods

rnf :: Message m -> () #

Decode m => DecodeWire (Message m) Source # 
(Foldable f, Encode m) => EncodeWire (f (Message m)) Source # 

Methods

encodeWire :: Tag -> f (Message m) -> Put Source #

HasField (Field n (RepeatedField [Message a])) Source #

Iso: FieldType (Repeated n (Message a)) = [a]

HasField (Field n (OptionalField (Maybe (Message a)))) Source #

Iso: FieldType (Optional n (Message a)) = Maybe a

HasField (Field n (RequiredField (Always (Message a)))) Source #

Iso: FieldType (Required n (Message a)) = a

(Decode a, Monoid (Message a), KnownNat n) => GDecode (K1 * i (Field n (OptionalField (Maybe (Message a))))) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 * i (Field n (OptionalField (Maybe (Message a)))) a)

(Decode a, Monoid (Message a), KnownNat n) => GDecode (K1 * i (Field n (RequiredField (Always (Message a))))) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 * i (Field n (RequiredField (Always (Message a)))) a)

type Required n (Message a) Source # 
type Optional n (Message a) Source # 
type FieldType (Field n (RepeatedField [Message a])) Source # 
type FieldType (Field n (RepeatedField [Message a])) = [a]
type FieldType (Field n (OptionalField (Maybe (Message a)))) Source # 
type FieldType (Field n (RequiredField (Always (Message a)))) Source # 

class GDecode (f :: * -> *) Source #

Minimal complete definition

gdecode

Instances

GDecode (U1 *) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (U1 * a)

(DecodeWire (PackedList a), KnownNat n) => GDecode (K1 * i (Packed n a)) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 * i (Packed n a) a)

(DecodeWire a, KnownNat n) => GDecode (K1 * i (Field n (RequiredField (Always (Value a))))) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 * i (Field n (RequiredField (Always (Value a)))) a)

(DecodeWire a, KnownNat n) => GDecode (K1 * i (Repeated n a)) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 * i (Repeated n a) a)

(Enum a, KnownNat n) => GDecode (K1 * i (Field n (OptionalField (Last (Enumeration a))))) Source # 
(Enum a, KnownNat n) => GDecode (K1 * i (Field n (RequiredField (Always (Enumeration a))))) Source # 
(DecodeWire a, KnownNat n) => GDecode (K1 * i (Field n (OptionalField (Last (Value a))))) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 * i (Field n (OptionalField (Last (Value a)))) a)

(Decode a, Monoid (Message a), KnownNat n) => GDecode (K1 * i (Field n (OptionalField (Maybe (Message a))))) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 * i (Field n (OptionalField (Maybe (Message a)))) a)

(Decode a, Monoid (Message a), KnownNat n) => GDecode (K1 * i (Field n (RequiredField (Always (Message a))))) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 * i (Field n (RequiredField (Always (Message a)))) a)

(GDecode x, GDecode y) => GDecode ((:+:) * x y) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get ((* :+: x) y a)

(GDecode a, GDecode b) => GDecode ((:*:) * a b) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get ((* :*: a) b a)

GDecode a => GDecode (M1 * i c a) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (M1 * i c a a)

class GEncode (f :: * -> *) Source #

Minimal complete definition

gencode

Instances

GEncode (U1 *) Source # 

Methods

gencode :: U1 * a -> Put

(EncodeWire a, KnownNat n, Foldable f) => GEncode (K1 * i (Field n (f a))) Source # 

Methods

gencode :: K1 * i (Field n (f a)) a -> Put

(GEncode a, GEncode b) => GEncode ((:+:) * a b) Source # 

Methods

gencode :: (* :+: a) b a -> Put

(GEncode a, GEncode b) => GEncode ((:*:) * a b) Source # 

Methods

gencode :: (* :*: a) b a -> Put

GEncode a => GEncode (M1 * i c a) Source # 

Methods

gencode :: M1 * i c a a -> Put

class GMessageMonoid (f :: * -> *) Source #

Minimal complete definition

gmempty, gmappend

Instances

GMessageMonoid (U1 *) Source # 

Methods

gmempty :: U1 * a

gmappend :: U1 * a -> U1 * a -> U1 * a

Monoid c => GMessageMonoid (K1 * i c) Source # 

Methods

gmempty :: K1 * i c a

gmappend :: K1 * i c a -> K1 * i c a -> K1 * i c a

(GMessageMonoid x, GMessageMonoid y) => GMessageMonoid ((:+:) * x y) Source # 

Methods

gmempty :: (* :+: x) y a

gmappend :: (* :+: x) y a -> (* :+: x) y a -> (* :+: x) y a

(GMessageMonoid x, GMessageMonoid y) => GMessageMonoid ((:*:) * x y) Source # 

Methods

gmempty :: (* :*: x) y a

gmappend :: (* :*: x) y a -> (* :*: x) y a -> (* :*: x) y a

GMessageMonoid f => GMessageMonoid (M1 * i c f) Source # 

Methods

gmempty :: M1 * i c f a

gmappend :: M1 * i c f a -> M1 * i c f a -> M1 * i c f a