Safe Haskell | None |
---|---|
Language | Haskell2010 |
Tutorial
This module contains a worked example of encoding and decoding messages, and exporting a corresponding .proto file from Haskell types.
Setup
If you are using GHC.Generics, you should enable the generic deriving extension, and import the main module:
{-# LANGUAGE DeriveGeneric #-}
import Proto3.Suite import GHC.Generics
Documentation
>>>
:set -XOverloadedStrings
Defining Message Types
Define messages using Haskell record types. You can use any MessageField
types
in your records, and the correct serializer and deserializer will be generated
for you.
Make sure to derive a Generic
instance for your type, and then derive instances
for Message
and Named
using the default (empty) instances:
instance Message Foo instance Named Foo
Encoding Messages
Now we can encode a value of type Foo
using toLazyByteString
.
For example:
>>>
Proto3.Suite.toLazyByteString (Foo 42 (Proto3.Suite.PackedVec (pure 123)))
"\b*\DC2\SOH{"
We can also decode messages using fromByteString
:
>>>
Proto3.Suite.fromByteString "\b*\DC2\SOH{" :: Either Proto3.Wire.Decode.ParseError Foo
Right (Foo {fooX = 42, fooY = PackedVec {packedvec = [123]}})
Instances
Eq Foo Source # | |
Show Foo Source # | |
Generic Foo Source # | |
Message Foo Source # | |
Defined in Proto3.Suite.Tutorial encodeMessage :: FieldNumber -> Foo -> MessageBuilder Source # decodeMessage :: FieldNumber -> Parser RawMessage Foo Source # | |
Named Foo Source # | |
type Rep Foo Source # | |
Defined in Proto3.Suite.Tutorial type Rep Foo = D1 ('MetaData "Foo" "Proto3.Suite.Tutorial" "proto3-suite-0.7.0-inplace" 'False) (C1 ('MetaCons "Foo" 'PrefixI 'True) (S1 ('MetaSel ('Just "fooX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32) :*: S1 ('MetaSel ('Just "fooY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PackedVec Int32)))) |
Nested Messages
Messages can contain other messages, by using the Nested
constructor, and
lists of nested messages using the 'NestedVec constructor'.
Instances
Eq Bar Source # | |
Generic Bar Source # | |
Message Bar Source # | |
Defined in Proto3.Suite.Tutorial encodeMessage :: FieldNumber -> Bar -> MessageBuilder Source # decodeMessage :: FieldNumber -> Parser RawMessage Bar Source # | |
Named Bar Source # | |
type Rep Bar Source # | |
Defined in Proto3.Suite.Tutorial type Rep Bar = D1 ('MetaData "Bar" "Proto3.Suite.Tutorial" "proto3-suite-0.7.0-inplace" 'False) (C1 ('MetaCons "Bar" 'PrefixI 'True) (S1 ('MetaSel ('Just "barShape") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Enumerated Shape)) :*: (S1 ('MetaSel ('Just "barFoo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Nested Foo)) :*: S1 ('MetaSel ('Just "foos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NestedVec Foo))))) |
Enumerations
Enumerated types can be used by deriving the Bounded
, Enum
, ProtoEnum
,
Finite
, and Named
classes. Each of these instances are implied by
a Generic
instance, so can be derived as follows:
data Shape = Circle | Square | Triangle deriving (Bounded, Eq, Enum, Finite, Generic, Named, Ord, ProtoEnum)
Instances
Bounded Shape Source # | |
Enum Shape Source # | |
Defined in Proto3.Suite.Tutorial succ :: Shape -> Shape Source # pred :: Shape -> Shape Source # toEnum :: Int -> Shape Source # fromEnum :: Shape -> Int Source # enumFrom :: Shape -> [Shape] Source # enumFromThen :: Shape -> Shape -> [Shape] Source # enumFromTo :: Shape -> Shape -> [Shape] Source # enumFromThenTo :: Shape -> Shape -> Shape -> [Shape] Source # | |
Eq Shape Source # | |
Ord Shape Source # | |
Defined in Proto3.Suite.Tutorial | |
Generic Shape Source # | |
ProtoEnum Shape Source # | |
Defined in Proto3.Suite.Tutorial | |
Finite Shape Source # | |
Named Shape Source # | |
type Rep Shape Source # | |
Defined in Proto3.Suite.Tutorial |
Generating a .proto file
We can generate a .proto file for the Foo
and Bar
data types by
using the toProtoFileDef
function. We have to provide a package name, and
explicitly list the message and enumeration types as a DotProto
value.
>>>
putStrLn protoFile
syntax = "proto3"; package examplePackageName; enum Shape { Circle = 0; Square = 1; Triangle = 2; } message Foo { uint32 fooX = 1; repeated int32 fooY = 2 [packed = true]; } message Bar { Shape barShape = 1; Foo barFoo = 2; repeated Foo foos = 3; }