lol-0.7.0.0: A library for lattice cryptography.

Copyright(c) Eric Crockett 2011-2017
Chris Peikert 2011-2017
LicenseGPL-3
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.

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 # 
Instance details

Defined in Crypto.Lol.Types.Proto

Associated Types

type ProtoType Fingerprint :: Type Source #

Protoable a => Protoable [a] Source # 
Instance details

Defined in Crypto.Lol.Types.Proto

Associated Types

type ProtoType [a] :: Type Source #

Methods

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

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

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

Defined in Crypto.Lol.Types.Proto

Associated Types

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

Methods

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

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

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

Defined in Crypto.Lol.Types.IZipVector

Associated Types

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

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

Defined in Crypto.Lol.Types.IZipVector

Associated Types

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

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

Defined in Crypto.Lol.Types.IZipVector

Associated Types

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

(Fact m, Reflects q Int64) => Protoable (IZipVector m (ZqBasic q Int64)) Source # 
Instance details

Defined in Crypto.Lol.Types.IZipVector

Associated Types

type ProtoType (IZipVector m (ZqBasic q Int64)) :: Type Source #

Fact m => Protoable (IZipVector m Double) Source # 
Instance details

Defined in Crypto.Lol.Types.IZipVector

Associated Types

type ProtoType (IZipVector m Double) :: Type Source #

Fact m => Protoable (IZipVector m Int64) Source # 
Instance details

Defined in Crypto.Lol.Types.IZipVector

Associated Types

type ProtoType (IZipVector m Int64) :: Type Source #

(Fact m, CRTElt t Double, TensorPowDec t (RRq q Double), Protoable (CycRep t D m (RRq q Double))) => Protoable (Cyc t m (RRq q Double)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Associated Types

type ProtoType (Cyc t m (RRq q Double)) :: Type Source #

Methods

toProto :: Cyc t m (RRq q Double) -> ProtoType (Cyc t m (RRq q Double)) Source #

fromProto :: MonadError String m0 => ProtoType (Cyc t m (RRq q Double)) -> m0 (Cyc t m (RRq q Double)) Source #

(Fact m, CRTElt t Double, Protoable (CycG t m (ZqBasic q z))) => Protoable (Cyc t m (ZqBasic q z)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Associated Types

type ProtoType (Cyc t m (ZqBasic q z)) :: Type Source #

Methods

toProto :: Cyc t m (ZqBasic q z) -> ProtoType (Cyc t m (ZqBasic q z)) Source #

fromProto :: MonadError String m0 => ProtoType (Cyc t m (ZqBasic q z)) -> m0 (Cyc t m (ZqBasic q z)) Source #

(Fact m, CRTElt t Int64, Protoable (CycG t m Int64)) => Protoable (Cyc t m Int64) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Associated Types

type ProtoType (Cyc t m Int64) :: Type Source #

Methods

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

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

(Fact m, CRTElt t Double, Protoable (CycG t m Double)) => Protoable (Cyc t m Double) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Associated Types

type ProtoType (Cyc t m Double) :: Type Source #

Protoable (t m r) => Protoable (CycRep t D m r) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.CycRep

Associated Types

type ProtoType (CycRep t D m r) :: Type Source #

Methods

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

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

(Reflects e Word32, Reflects r Word32, Protoable (c s zq), ProtoType (c s zq) ~ RqProduct) => Protoable (Linear c e r s zq) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Linear

Associated Types

type ProtoType (Linear c e r s zq) :: Type Source #

Methods

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

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