grapesy
Safe HaskellNone
LanguageHaskell2010

Network.GRPC.Common.Compression

Description

Public Compression API

Intended for qualified import.

import Network.GRPC.Common.Compression (Compression(..))
import Network.GRPC.Common.Compression qualified as Compr
Synopsis

Definition

data CompressionId #

Instances

Instances details
IsString CompressionId 
Instance details

Defined in Network.GRPC.Spec.Compression

Generic CompressionId 
Instance details

Defined in Network.GRPC.Spec.Compression

Associated Types

type Rep CompressionId 
Instance details

Defined in Network.GRPC.Spec.Compression

type Rep CompressionId = D1 ('MetaData "CompressionId" "Network.GRPC.Spec.Compression" "grpc-spec-1.0.0-inplace" 'False) ((C1 ('MetaCons "Identity" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GZip" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Deflate" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Snappy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Custom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))
Show CompressionId 
Instance details

Defined in Network.GRPC.Spec.Compression

Eq CompressionId 
Instance details

Defined in Network.GRPC.Spec.Compression

Ord CompressionId 
Instance details

Defined in Network.GRPC.Spec.Compression

type Rep CompressionId 
Instance details

Defined in Network.GRPC.Spec.Compression

type Rep CompressionId = D1 ('MetaData "CompressionId" "Network.GRPC.Spec.Compression" "grpc-spec-1.0.0-inplace" 'False) ((C1 ('MetaCons "Identity" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GZip" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Deflate" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Snappy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Custom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))

Standard compression schemes

Negotation

data Negotation Source #

Compression negotation

Constructors

Negotation 

Fields

  • offer :: NonEmpty CompressionId

    Which algorithms should be offered (in this order) to the peer?

    This should normally always include Identity (see choose); but see insist.

  • choose :: NonEmpty CompressionId -> Compression

    Choose compression algorithm

    We will run this only once per open connection, when the server first tells us their list of supported compression algorithms. Unless compression negotation has taken place, no compression should be used.

    This cannot fail: the least common denominator is to use no compression. This must be allowed, because the gRPC specification anyway allows a per-message flag to indicate whether the message is compressed or not; thus, even if a specific compression algorithm is negotiated, there is no guarantee anything is compressed.

  • supported :: Map CompressionId Compression

    All supported compression algorithms

Instances

Instances details
Default Negotation Source # 
Instance details

Defined in Network.GRPC.Common.Compression

Methods

def :: Negotation #

Specific negotation strategies

none :: Negotation Source #

Disable all compression

chooseFirst :: NonEmpty Compression -> Negotation Source #

Choose the first algorithm that appears in the list of peer supported

Precondition: the list should include the identity.

only :: Compression -> Negotation Source #

Only use the given algorithm, if the peer supports it

insist :: Compression -> Negotation Source #

Insist on the specified algorithm, no matter what the peer offers

This is dangerous: if the peer does not support the specified algorithm, it will be unable to decompress any messages. Primarily used for testing.

See also only.