lol-0.4.0.0: A library for lattice cryptography.

Safe HaskellNone
LanguageHaskell2010

Crypto.Lol.Types.Proto

Description

Convenient interfaces for serialization with protocol buffers.

Synopsis

Documentation

class Protoable a where Source #

Conversion between Haskell types and their protocol buffer representations.

Minimal complete definition

toProto, fromProto

Associated Types

type ProtoType a Source #

The protocol buffer type for a.

Methods

toProto :: a -> ProtoType a Source #

Convert from a type to its protocol buffer representation.

fromProto :: MonadError String m => ProtoType a -> m a Source #

Convert from a protocol buffer representation.

Instances

Protoable a => Protoable [a] Source # 

Associated Types

type ProtoType [a] :: * Source #

Methods

toProto :: [a] -> ProtoType [a] Source #

fromProto :: MonadError String m => ProtoType [a] -> m [a] Source #

(Protoable a, Protoable b) => Protoable (a, b) Source # 

Associated Types

type ProtoType (a, b) :: * Source #

Methods

toProto :: (a, b) -> ProtoType (a, b) Source #

fromProto :: MonadError String m => ProtoType (a, b) -> m (a, b) Source #

(Fact m, Reflects k q Double) => Protoable (CT m (RRq k q Double)) Source # 

Associated Types

type ProtoType (CT m (RRq k q Double)) :: * Source #

Methods

toProto :: CT m (RRq k q Double) -> ProtoType (CT m (RRq k q Double)) Source #

fromProto :: MonadError String m => ProtoType (CT m (RRq k q Double)) -> m (CT m (RRq k q Double)) Source #

(Fact m, Reflects k q Int64) => Protoable (CT m (ZqBasic k q Int64)) Source # 

Associated Types

type ProtoType (CT m (ZqBasic k q Int64)) :: * Source #

Methods

toProto :: CT m (ZqBasic k q Int64) -> ProtoType (CT m (ZqBasic k q Int64)) Source #

fromProto :: MonadError String m => ProtoType (CT m (ZqBasic k q Int64)) -> m (CT m (ZqBasic k q Int64)) Source #

(Fact m, Reflects k q Double) => Protoable (RT m (RRq k q Double)) Source # 

Associated Types

type ProtoType (RT m (RRq k q Double)) :: * Source #

Methods

toProto :: RT m (RRq k q Double) -> ProtoType (RT m (RRq k q Double)) Source #

fromProto :: MonadError String m => ProtoType (RT m (RRq k q Double)) -> m (RT m (RRq k q Double)) Source #

(Fact m, Reflects k q Int64) => Protoable (RT m (ZqBasic k q Int64)) Source # 

Associated Types

type ProtoType (RT m (ZqBasic k q Int64)) :: * Source #

Methods

toProto :: RT m (ZqBasic k q Int64) -> ProtoType (RT m (ZqBasic k q Int64)) Source #

fromProto :: MonadError String m => ProtoType (RT m (ZqBasic k q Int64)) -> m (RT m (ZqBasic k q Int64)) Source #

(Fact m, CElt t r, Protoable (UCyc t m D r)) => Protoable (Cyc t m r) Source # 

Associated Types

type ProtoType (Cyc t m r) :: * Source #

Methods

toProto :: Cyc t m r -> ProtoType (Cyc t m r) Source #

fromProto :: MonadError String m => ProtoType (Cyc t m r) -> m (Cyc t m r) Source #

Protoable (t m r) => Protoable (UCyc t m D r) Source # 

Associated Types

type ProtoType (UCyc t m D r) :: * Source #

Methods

toProto :: UCyc t m D r -> ProtoType (UCyc t m D r) Source #

fromProto :: MonadError String m => ProtoType (UCyc t m D r) -> m (UCyc t m D r) Source #

msgPut :: (ReflectDescriptor (ProtoType a), Wire (ProtoType a), Protoable a) => a -> ByteString Source #

Serialize a Haskell type to its protocol buffer ByteString.

msgGet :: (ReflectDescriptor (ProtoType a), Wire (ProtoType a), Protoable a) => ByteString -> Either String (a, ByteString) Source #

Read a protocol buffer ByteString to a Haskell type.