| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Proto3.Suite.Types
Synopsis
- newtype Fixed a = Fixed {
- fixed :: a
- newtype Signed a = Signed {
- signed :: a
- newtype Enumerated a = Enumerated {
- enumerated :: Either Int32 a
- newtype String a = String {
- string :: a
- newtype Bytes a = Bytes {
- bytes :: a
- newtype ForceEmit a = ForceEmit {
- forceEmit :: a
- newtype Nested a = Nested {}
- newtype UnpackedVec a = UnpackedVec {
- unpackedvec :: Vector a
- newtype PackedVec a = PackedVec {}
- newtype NestedVec a = NestedVec {}
- newtype Commented (comment :: Symbol) a = Commented {
- unCommented :: a
- type (//) a (comment :: Symbol) = Commented comment a
Integral Types
Fixed provides a way to encode integers in the fixed-width wire formats.
Instances
Signed provides a way to encode integers in the signed wire formats.
Instances
Enumerable Types
newtype Enumerated a Source #
Enumerated lifts any type with an IsEnum instance so that it can be encoded
with HasEncoding.
Constructors
| Enumerated | |
Fields
| |
Instances
String and Bytes Types
String provides a way to indicate that the given type expresses
a Protobuf string scalar. may have type class instances
that are more specific to Protobuf uses than those of String aa.
Instances
Bytes provides a way to indicate that the given type expresses
a Protobuf bytes scalar. may have type class instances
that are more specific to Protobuf uses than those of Bytes aa.
Instances
ForceEmit provides a way to force emission of field values, even when
default-value semantics states otherwise. Used when serializing oneof
subfields.
Instances
Nested provides a way to nest protobuf messages within protobuf messages.
Instances
newtype UnpackedVec a Source #
Constructors
| UnpackedVec | |
Fields
| |
Instances
PackedVec provides a way to encode packed lists of basic protobuf types into
the wire format.
Instances
Instances
newtype Commented (comment :: Symbol) a Source #
Commented provides a way to add comments to generated .proto files.
Constructors
| Commented | |
Fields
| |
Instances
| Functor (Commented comment) Source # | |
| Foldable (Commented comment) Source # | |
Defined in Proto3.Suite.Types Methods fold :: Monoid m => Commented comment m -> m Source # foldMap :: Monoid m => (a -> m) -> Commented comment a -> m Source # foldMap' :: Monoid m => (a -> m) -> Commented comment a -> m Source # foldr :: (a -> b -> b) -> b -> Commented comment a -> b Source # foldr' :: (a -> b -> b) -> b -> Commented comment a -> b Source # foldl :: (b -> a -> b) -> b -> Commented comment a -> b Source # foldl' :: (b -> a -> b) -> b -> Commented comment a -> b Source # foldr1 :: (a -> a -> a) -> Commented comment a -> a Source # foldl1 :: (a -> a -> a) -> Commented comment a -> a Source # toList :: Commented comment a -> [a] Source # null :: Commented comment a -> Bool Source # length :: Commented comment a -> Int Source # elem :: Eq a => a -> Commented comment a -> Bool Source # maximum :: Ord a => Commented comment a -> a Source # minimum :: Ord a => Commented comment a -> a Source # | |
| Traversable (Commented comment) Source # | |
Defined in Proto3.Suite.Types Methods traverse :: Applicative f => (a -> f b) -> Commented comment a -> f (Commented comment b) Source # sequenceA :: Applicative f => Commented comment (f a) -> f (Commented comment a) Source # mapM :: Monad m => (a -> m b) -> Commented comment a -> m (Commented comment b) Source # sequence :: Monad m => Commented comment (m a) -> m (Commented comment a) Source # | |
| Eq a => Eq (Commented comment a) Source # | |
| Ord a => Ord (Commented comment a) Source # | |
Defined in Proto3.Suite.Types Methods compare :: Commented comment a -> Commented comment a -> Ordering Source # (<) :: Commented comment a -> Commented comment a -> Bool Source # (<=) :: Commented comment a -> Commented comment a -> Bool Source # (>) :: Commented comment a -> Commented comment a -> Bool Source # (>=) :: Commented comment a -> Commented comment a -> Bool Source # max :: Commented comment a -> Commented comment a -> Commented comment a Source # min :: Commented comment a -> Commented comment a -> Commented comment a Source # | |
| Show a => Show (Commented comment a) Source # | |
| Generic (Commented comment a) Source # | |
| Semigroup a => Semigroup (Commented comment a) Source # | |
| Monoid a => Monoid (Commented comment a) Source # | |
| Arbitrary a => Arbitrary (Commented comment a) Source # | |
| NFData a => NFData (Commented comment a) Source # | |
Defined in Proto3.Suite.Types | |
| (MessageField e, KnownSymbol comments) => MessageField (e // comments) Source # | |
Defined in Proto3.Suite.Class Methods encodeMessageField :: FieldNumber -> (e // comments) -> MessageBuilder Source # decodeMessageField :: Parser RawField (e // comments) Source # protoType :: Proxy# (e // comments) -> DotProtoField Source # | |
| type Rep (Commented comment a) Source # | |
Defined in Proto3.Suite.Types | |