proto3-suite-0.7.0: A higher-level API to the proto3-wire library
Safe HaskellNone
LanguageHaskell2010

Proto3.Suite.Tutorial

Description

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
Synopsis

Documentation

>>> :set -XOverloadedStrings

data Foo Source #

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]}})

Constructors

Foo 

Fields

Instances

Instances details
Eq Foo Source # 
Instance details

Defined in Proto3.Suite.Tutorial

Methods

(==) :: Foo -> Foo -> Bool Source #

(/=) :: Foo -> Foo -> Bool Source #

Show Foo Source # 
Instance details

Defined in Proto3.Suite.Tutorial

Generic Foo Source # 
Instance details

Defined in Proto3.Suite.Tutorial

Associated Types

type Rep Foo :: Type -> Type Source #

Methods

from :: Foo -> Rep Foo x Source #

to :: Rep Foo x -> Foo Source #

Message Foo Source # 
Instance details

Defined in Proto3.Suite.Tutorial

Named Foo Source # 
Instance details

Defined in Proto3.Suite.Tutorial

Methods

nameOf :: IsString string => Proxy# Foo -> string Source #

type Rep Foo Source # 
Instance details

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

data Bar Source #

Nested Messages

Messages can contain other messages, by using the Nested constructor, and lists of nested messages using the 'NestedVec constructor'.

Constructors

Bar 

Instances

Instances details
Eq Bar Source # 
Instance details

Defined in Proto3.Suite.Tutorial

Methods

(==) :: Bar -> Bar -> Bool Source #

(/=) :: Bar -> Bar -> Bool Source #

Generic Bar Source # 
Instance details

Defined in Proto3.Suite.Tutorial

Associated Types

type Rep Bar :: Type -> Type Source #

Methods

from :: Bar -> Rep Bar x Source #

to :: Rep Bar x -> Bar Source #

Message Bar Source # 
Instance details

Defined in Proto3.Suite.Tutorial

Named Bar Source # 
Instance details

Defined in Proto3.Suite.Tutorial

Methods

nameOf :: IsString string => Proxy# Bar -> string Source #

type Rep Bar Source # 
Instance details

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

data Shape Source #

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)

Constructors

Circle 
Square 
Triangle 

Instances

Instances details
Bounded Shape Source # 
Instance details

Defined in Proto3.Suite.Tutorial

Enum Shape Source # 
Instance details

Defined in Proto3.Suite.Tutorial

Eq Shape Source # 
Instance details

Defined in Proto3.Suite.Tutorial

Methods

(==) :: Shape -> Shape -> Bool Source #

(/=) :: Shape -> Shape -> Bool Source #

Ord Shape Source # 
Instance details

Defined in Proto3.Suite.Tutorial

Generic Shape Source # 
Instance details

Defined in Proto3.Suite.Tutorial

Associated Types

type Rep Shape :: Type -> Type Source #

Methods

from :: Shape -> Rep Shape x Source #

to :: Rep Shape x -> Shape Source #

ProtoEnum Shape Source # 
Instance details

Defined in Proto3.Suite.Tutorial

Finite Shape Source # 
Instance details

Defined in Proto3.Suite.Tutorial

Methods

enumerate :: IsString string => Proxy# Shape -> [(string, Int32)] Source #

Named Shape Source # 
Instance details

Defined in Proto3.Suite.Tutorial

Methods

nameOf :: IsString string => Proxy# Shape -> string Source #

type Rep Shape Source # 
Instance details

Defined in Proto3.Suite.Tutorial

type Rep Shape = D1 ('MetaData "Shape" "Proto3.Suite.Tutorial" "proto3-suite-0.7.0-inplace" 'False) (C1 ('MetaCons "Circle" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Square" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Triangle" 'PrefixI 'False) (U1 :: Type -> Type)))

protoFile :: String Source #

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;
}