lol-0.6.0.0: A library for lattice cryptography.

Copyright(c) Eric Crockett 2011-2017
Chris Peikert 2011-2017
LicenseGPL-2
Maintainerecrockett0@email.com
Stabilityexperimental
PortabilityPOSIX
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 #

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 Fingerprint Source # 
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 #

(Protoable (IZipVector m (RRq k q Double)), (~) * (ProtoType (IZipVector m (RRq k q Double))) KqProduct, Protoable (IZipVector m b), (~) * (ProtoType (IZipVector m b)) KqProduct) => Protoable (IZipVector m (RRq k q Double, b)) Source # 

Associated Types

type ProtoType (IZipVector m (RRq k q Double, b)) :: * Source #

Methods

toProto :: IZipVector m (RRq k q Double, b) -> ProtoType (IZipVector m (RRq k q Double, b)) Source #

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

(Protoable (IZipVector m (ZqBasic k q Int64)), (~) * (ProtoType (IZipVector m (ZqBasic k q Int64))) RqProduct, Protoable (IZipVector m b), (~) * (ProtoType (IZipVector m b)) RqProduct) => Protoable (IZipVector m (ZqBasic k q Int64, b)) Source # 

Associated Types

type ProtoType (IZipVector m (ZqBasic k q Int64, b)) :: * Source #

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

Associated Types

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

(Fact m, Reflects k q Int64) => Protoable (IZipVector m (ZqBasic k q Int64)) Source # 
Fact m => Protoable (IZipVector m 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 #

(Reflects Factored e Word32, Reflects Factored r Word32, Protoable (Cyc t s zq), (~) * (ProtoType (t s zq)) RqProduct) => Protoable (Linear t zq e r s) Source # 

Associated Types

type ProtoType (Linear t zq e r s) :: * Source #

Methods

toProto :: Linear t zq e r s -> ProtoType (Linear t zq e r s) Source #

fromProto :: MonadError String m => ProtoType (Linear t zq e r s) -> m (Linear t zq e r s) 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.

readProtoType :: (ReflectDescriptor a, Wire a, MonadIO m, MonadError String m) => FilePath -> m a Source #

Read a serialized protobuffer from a file.

parseProtoFile :: (ProtoReadable a, MonadIO m, MonadError String m) => FilePath -> m a Source #

Read a protocol buffer stream at the given path and convert it to typed Haskell data.

writeProtoType :: (ReflectDescriptor a, Wire a) => FilePath -> a -> IO () Source #

Writes any auto-gen'd proto object to path/filename.

writeProtoFile :: (ProtoReadable a, MonadIO m) => FilePath -> a -> m () Source #

Write a protocol buffer stream for Haskell data to the given path.

type ProtoReadable a = (Protoable a, Wire (ProtoType a), ReflectDescriptor (ProtoType a)) Source #

Constraint synonym for end-to-end readingparsingwriting of Protoable types.