grapesy
Safe HaskellNone
LanguageHaskell2010

Network.GRPC.Common

Description

General infrastructure used by both the client and the server

Intended for unqualified import.

Synopsis

Abstraction over different serialization formats

class (NFData (Input rpc), NFData (Output rpc), Show (Input rpc), Show (Output rpc), Show (RequestMetadata rpc), Show (ResponseInitialMetadata rpc), Show (ResponseTrailingMetadata rpc)) => IsRPC (rpc :: k) where #

Instances

Instances details
(KnownSymbol serv, KnownSymbol meth, NFData (Input (JsonRpc serv meth)), NFData (Output (JsonRpc serv meth)), Show (Input (JsonRpc serv meth)), Show (Output (JsonRpc serv meth)), Show (RequestMetadata (JsonRpc serv meth)), Show (ResponseInitialMetadata (JsonRpc serv meth)), Show (ResponseTrailingMetadata (JsonRpc serv meth))) => IsRPC (JsonRpc serv meth :: Type) 
Instance details

Defined in Network.GRPC.Spec.RPC.JSON

(HasMethodImpl serv meth, Show (MethodInput serv meth), Show (MethodOutput serv meth), NFData (MethodInput serv meth), NFData (MethodOutput serv meth), Show (RequestMetadata (Protobuf serv meth)), Show (ResponseInitialMetadata (Protobuf serv meth)), Show (ResponseTrailingMetadata (Protobuf serv meth))) => IsRPC (Protobuf serv meth :: Type) 
Instance details

Defined in Network.GRPC.Spec.RPC.Protobuf

(KnownSymbol serv, KnownSymbol meth, Show (RequestMetadata (RawRpc serv meth)), Show (ResponseInitialMetadata (RawRpc serv meth)), Show (ResponseTrailingMetadata (RawRpc serv meth))) => IsRPC (RawRpc serv meth :: Type) 
Instance details

Defined in Network.GRPC.Spec.RPC.Raw

type family Input (rpc :: k) #

Instances

Instances details
type Input (Protobuf serv meth :: Type) 
Instance details

Defined in Network.GRPC.Spec.RPC.Protobuf

type Input (Protobuf serv meth :: Type) = Proto (MethodInput serv meth)
type Input (RawRpc serv meth :: Type) 
Instance details

Defined in Network.GRPC.Spec.RPC.Raw

type Input (RawRpc serv meth :: Type) = ByteString

type family Output (rpc :: k) #

Instances

Instances details
type Output (Protobuf serv meth :: Type) 
Instance details

Defined in Network.GRPC.Spec.RPC.Protobuf

type Output (Protobuf serv meth :: Type) = Proto (MethodOutput serv meth)
type Output (RawRpc serv meth :: Type) 
Instance details

Defined in Network.GRPC.Spec.RPC.Raw

type Output (RawRpc serv meth :: Type) = ByteString

class (IsRPC rpc, BuildMetadata (RequestMetadata rpc), ParseMetadata (ResponseInitialMetadata rpc), ParseMetadata (ResponseTrailingMetadata rpc)) => SupportsClientRpc (rpc :: k) where #

Instances

Instances details
(IsRPC (JsonRpc serv meth), ToJSON (Input (JsonRpc serv meth)), FromJSON (Output (JsonRpc serv meth)), BuildMetadata (RequestMetadata (JsonRpc serv meth)), ParseMetadata (ResponseInitialMetadata (JsonRpc serv meth)), ParseMetadata (ResponseTrailingMetadata (JsonRpc serv meth))) => SupportsClientRpc (JsonRpc serv meth :: Type) 
Instance details

Defined in Network.GRPC.Spec.RPC.JSON

Methods

rpcSerializeInput :: Proxy (JsonRpc serv meth) -> Input (JsonRpc serv meth) -> ByteString #

rpcDeserializeOutput :: Proxy (JsonRpc serv meth) -> ByteString -> Either String (Output (JsonRpc serv meth)) #

(IsRPC (Protobuf serv meth), HasMethodImpl serv meth, BuildMetadata (RequestMetadata (Protobuf serv meth)), ParseMetadata (ResponseInitialMetadata (Protobuf serv meth)), ParseMetadata (ResponseTrailingMetadata (Protobuf serv meth))) => SupportsClientRpc (Protobuf serv meth :: Type) 
Instance details

Defined in Network.GRPC.Spec.RPC.Protobuf

Methods

rpcSerializeInput :: Proxy (Protobuf serv meth) -> Input (Protobuf serv meth) -> ByteString #

rpcDeserializeOutput :: Proxy (Protobuf serv meth) -> ByteString -> Either String (Output (Protobuf serv meth)) #

(IsRPC (RawRpc serv meth), BuildMetadata (RequestMetadata (RawRpc serv meth)), ParseMetadata (ResponseInitialMetadata (RawRpc serv meth)), ParseMetadata (ResponseTrailingMetadata (RawRpc serv meth))) => SupportsClientRpc (RawRpc serv meth :: Type) 
Instance details

Defined in Network.GRPC.Spec.RPC.Raw

Methods

rpcSerializeInput :: Proxy (RawRpc serv meth) -> Input (RawRpc serv meth) -> ByteString #

rpcDeserializeOutput :: Proxy (RawRpc serv meth) -> ByteString -> Either String (Output (RawRpc serv meth)) #

class (IsRPC rpc, ParseMetadata (RequestMetadata rpc), BuildMetadata (ResponseInitialMetadata rpc), StaticMetadata (ResponseTrailingMetadata rpc)) => SupportsServerRpc (rpc :: k) where #

Instances

Instances details
(IsRPC (JsonRpc serv meth), FromJSON (Input (JsonRpc serv meth)), ToJSON (Output (JsonRpc serv meth)), ParseMetadata (RequestMetadata (JsonRpc serv meth)), BuildMetadata (ResponseInitialMetadata (JsonRpc serv meth)), StaticMetadata (ResponseTrailingMetadata (JsonRpc serv meth))) => SupportsServerRpc (JsonRpc serv meth :: Type) 
Instance details

Defined in Network.GRPC.Spec.RPC.JSON

Methods

rpcDeserializeInput :: Proxy (JsonRpc serv meth) -> ByteString -> Either String (Input (JsonRpc serv meth)) #

rpcSerializeOutput :: Proxy (JsonRpc serv meth) -> Output (JsonRpc serv meth) -> ByteString #

(IsRPC (Protobuf serv meth), HasMethodImpl serv meth, ParseMetadata (RequestMetadata (Protobuf serv meth)), BuildMetadata (ResponseInitialMetadata (Protobuf serv meth)), StaticMetadata (ResponseTrailingMetadata (Protobuf serv meth))) => SupportsServerRpc (Protobuf serv meth :: Type) 
Instance details

Defined in Network.GRPC.Spec.RPC.Protobuf

Methods

rpcDeserializeInput :: Proxy (Protobuf serv meth) -> ByteString -> Either String (Input (Protobuf serv meth)) #

rpcSerializeOutput :: Proxy (Protobuf serv meth) -> Output (Protobuf serv meth) -> ByteString #

(IsRPC (RawRpc serv meth), ParseMetadata (RequestMetadata (RawRpc serv meth)), BuildMetadata (ResponseInitialMetadata (RawRpc serv meth)), StaticMetadata (ResponseTrailingMetadata (RawRpc serv meth))) => SupportsServerRpc (RawRpc serv meth :: Type) 
Instance details

Defined in Network.GRPC.Spec.RPC.Raw

Methods

rpcDeserializeInput :: Proxy (RawRpc serv meth) -> ByteString -> Either String (Input (RawRpc serv meth)) #

rpcSerializeOutput :: Proxy (RawRpc serv meth) -> Output (RawRpc serv meth) -> ByteString #

Stream elements

data StreamElem b a Source #

An element positioned in a stream

Constructors

StreamElem !a

Element in the stream

The final element in a stream may or may not be marked as final; if it is not, we will only discover after receiving the final element that it was in fact final. Moreover, we do not know ahead of time whether or not the final element will be marked.

When we receive an element and it is not marked final, this might therefore mean one of two things, without being able to tell which:

  • We are dealing with a stream in which the final element is not marked.

In this case, the element may or may not be the final element; if it is, the next value will be NoMoreElems (but waiting for the next value might mean a blocking call).

  • We are dealing with a stream in which the final element is marked.

In this case, this element is not final (and the final element, when we receive it, will be tagged as Final).

FinalElem !a !b

We received the final element

The final element is annotated with some additional information.

NoMoreElems !b

There are no more elements

This is used in two situations:

  • The stream didn't contain any elements at all.
  • The final element was not marked as final. See StreamElem for detailed additional discussion.

Instances

Instances details
Bifoldable StreamElem Source # 
Instance details

Defined in Network.GRPC.Common.StreamElem

Methods

bifold :: Monoid m => StreamElem m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> StreamElem a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> StreamElem a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> StreamElem a b -> c #

Bifunctor StreamElem Source # 
Instance details

Defined in Network.GRPC.Common.StreamElem

Methods

bimap :: (a -> b) -> (c -> d) -> StreamElem a c -> StreamElem b d #

first :: (a -> b) -> StreamElem a c -> StreamElem b c #

second :: (b -> c) -> StreamElem a b -> StreamElem a c #

Bitraversable StreamElem Source # 
Instance details

Defined in Network.GRPC.Common.StreamElem

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> StreamElem a b -> f (StreamElem c d) #

Functor (StreamElem b) Source # 
Instance details

Defined in Network.GRPC.Common.StreamElem

Methods

fmap :: (a -> b0) -> StreamElem b a -> StreamElem b b0 #

(<$) :: a -> StreamElem b b0 -> StreamElem b a #

Foldable (StreamElem b) Source # 
Instance details

Defined in Network.GRPC.Common.StreamElem

Methods

fold :: Monoid m => StreamElem b m -> m #

foldMap :: Monoid m => (a -> m) -> StreamElem b a -> m #

foldMap' :: Monoid m => (a -> m) -> StreamElem b a -> m #

foldr :: (a -> b0 -> b0) -> b0 -> StreamElem b a -> b0 #

foldr' :: (a -> b0 -> b0) -> b0 -> StreamElem b a -> b0 #

foldl :: (b0 -> a -> b0) -> b0 -> StreamElem b a -> b0 #

foldl' :: (b0 -> a -> b0) -> b0 -> StreamElem b a -> b0 #

foldr1 :: (a -> a -> a) -> StreamElem b a -> a #

foldl1 :: (a -> a -> a) -> StreamElem b a -> a #

toList :: StreamElem b a -> [a] #

null :: StreamElem b a -> Bool #

length :: StreamElem b a -> Int #

elem :: Eq a => a -> StreamElem b a -> Bool #

maximum :: Ord a => StreamElem b a -> a #

minimum :: Ord a => StreamElem b a -> a #

sum :: Num a => StreamElem b a -> a #

product :: Num a => StreamElem b a -> a #

Traversable (StreamElem b) Source # 
Instance details

Defined in Network.GRPC.Common.StreamElem

Methods

traverse :: Applicative f => (a -> f b0) -> StreamElem b a -> f (StreamElem b b0) #

sequenceA :: Applicative f => StreamElem b (f a) -> f (StreamElem b a) #

mapM :: Monad m => (a -> m b0) -> StreamElem b a -> m (StreamElem b b0) #

sequence :: Monad m => StreamElem b (m a) -> m (StreamElem b a) #

(Show a, Show b) => Show (StreamElem b a) Source # 
Instance details

Defined in Network.GRPC.Common.StreamElem

Methods

showsPrec :: Int -> StreamElem b a -> ShowS #

show :: StreamElem b a -> String #

showList :: [StreamElem b a] -> ShowS #

(Eq a, Eq b) => Eq (StreamElem b a) Source # 
Instance details

Defined in Network.GRPC.Common.StreamElem

Methods

(==) :: StreamElem b a -> StreamElem b a -> Bool #

(/=) :: StreamElem b a -> StreamElem b a -> Bool #

data NextElem a #

Constructors

NoNextElem 
NextElem !a 

Instances

Instances details
Functor NextElem 
Instance details

Defined in Network.GRPC.Spec.RPC.StreamType

Methods

fmap :: (a -> b) -> NextElem a -> NextElem b #

(<$) :: a -> NextElem b -> NextElem a #

Foldable NextElem 
Instance details

Defined in Network.GRPC.Spec.RPC.StreamType

Methods

fold :: Monoid m => NextElem m -> m #

foldMap :: Monoid m => (a -> m) -> NextElem a -> m #

foldMap' :: Monoid m => (a -> m) -> NextElem a -> m #

foldr :: (a -> b -> b) -> b -> NextElem a -> b #

foldr' :: (a -> b -> b) -> b -> NextElem a -> b #

foldl :: (b -> a -> b) -> b -> NextElem a -> b #

foldl' :: (b -> a -> b) -> b -> NextElem a -> b #

foldr1 :: (a -> a -> a) -> NextElem a -> a #

foldl1 :: (a -> a -> a) -> NextElem a -> a #

toList :: NextElem a -> [a] #

null :: NextElem a -> Bool #

length :: NextElem a -> Int #

elem :: Eq a => a -> NextElem a -> Bool #

maximum :: Ord a => NextElem a -> a #

minimum :: Ord a => NextElem a -> a #

sum :: Num a => NextElem a -> a #

product :: Num a => NextElem a -> a #

Traversable NextElem 
Instance details

Defined in Network.GRPC.Spec.RPC.StreamType

Methods

traverse :: Applicative f => (a -> f b) -> NextElem a -> f (NextElem b) #

sequenceA :: Applicative f => NextElem (f a) -> f (NextElem a) #

mapM :: Monad m => (a -> m b) -> NextElem a -> m (NextElem b) #

sequence :: Monad m => NextElem (m a) -> m (NextElem a) #

Show a => Show (NextElem a) 
Instance details

Defined in Network.GRPC.Spec.RPC.StreamType

Methods

showsPrec :: Int -> NextElem a -> ShowS #

show :: NextElem a -> String #

showList :: [NextElem a] -> ShowS #

Eq a => Eq (NextElem a) 
Instance details

Defined in Network.GRPC.Spec.RPC.StreamType

Methods

(==) :: NextElem a -> NextElem a -> Bool #

(/=) :: NextElem a -> NextElem a -> Bool #

Custom metadata

data CustomMetadata where #

Bundled Patterns

pattern CustomMetadata :: HasCallStack => HeaderName -> ByteString -> CustomMetadata 

Instances

Instances details
NFData CustomMetadata 
Instance details

Defined in Network.GRPC.Spec.CustomMetadata.Raw

Methods

rnf :: CustomMetadata -> () #

Generic CustomMetadata 
Instance details

Defined in Network.GRPC.Spec.CustomMetadata.Raw

Associated Types

type Rep CustomMetadata 
Instance details

Defined in Network.GRPC.Spec.CustomMetadata.Raw

type Rep CustomMetadata = D1 ('MetaData "CustomMetadata" "Network.GRPC.Spec.CustomMetadata.Raw" "grpc-spec-1.0.0-inplace" 'False) (C1 ('MetaCons "UnsafeCustomMetadata" 'PrefixI 'True) (S1 ('MetaSel ('Just "customMetadataName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HeaderName) :*: S1 ('MetaSel ('Just "customMetadataValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))
Show CustomMetadata 
Instance details

Defined in Network.GRPC.Spec.CustomMetadata.Raw

Eq CustomMetadata 
Instance details

Defined in Network.GRPC.Spec.CustomMetadata.Raw

type Rep CustomMetadata 
Instance details

Defined in Network.GRPC.Spec.CustomMetadata.Raw

type Rep CustomMetadata = D1 ('MetaData "CustomMetadata" "Network.GRPC.Spec.CustomMetadata.Raw" "grpc-spec-1.0.0-inplace" 'False) (C1 ('MetaCons "UnsafeCustomMetadata" 'PrefixI 'True) (S1 ('MetaSel ('Just "customMetadataName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HeaderName) :*: S1 ('MetaSel ('Just "customMetadataValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

data HeaderName where #

Bundled Patterns

pattern BinaryHeader :: HasCallStack => ByteString -> HeaderName 
pattern AsciiHeader :: HasCallStack => ByteString -> HeaderName 

Instances

Instances details
NFData HeaderName 
Instance details

Defined in Network.GRPC.Spec.CustomMetadata.Raw

Methods

rnf :: HeaderName -> () #

IsString HeaderName 
Instance details

Defined in Network.GRPC.Spec.CustomMetadata.Raw

Generic HeaderName 
Instance details

Defined in Network.GRPC.Spec.CustomMetadata.Raw

Associated Types

type Rep HeaderName 
Instance details

Defined in Network.GRPC.Spec.CustomMetadata.Raw

type Rep HeaderName = D1 ('MetaData "HeaderName" "Network.GRPC.Spec.CustomMetadata.Raw" "grpc-spec-1.0.0-inplace" 'False) (C1 ('MetaCons "UnsafeBinaryHeader" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)) :+: C1 ('MetaCons "UnsafeAsciiHeader" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))
Show HeaderName 
Instance details

Defined in Network.GRPC.Spec.CustomMetadata.Raw

Eq HeaderName 
Instance details

Defined in Network.GRPC.Spec.CustomMetadata.Raw

Ord HeaderName 
Instance details

Defined in Network.GRPC.Spec.CustomMetadata.Raw

type Rep HeaderName 
Instance details

Defined in Network.GRPC.Spec.CustomMetadata.Raw

type Rep HeaderName = D1 ('MetaData "HeaderName" "Network.GRPC.Spec.CustomMetadata.Raw" "grpc-spec-1.0.0-inplace" 'False) (C1 ('MetaCons "UnsafeBinaryHeader" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)) :+: C1 ('MetaCons "UnsafeAsciiHeader" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

Typed

type family RequestMetadata (rpc :: k) #

type family ResponseInitialMetadata (rpc :: k) #

type family ResponseTrailingMetadata (rpc :: k) #

Serialization

class BuildMetadata a where #

Methods

buildMetadata :: a -> [CustomMetadata] #

Instances

Instances details
BuildMetadata NoMetadata 
Instance details

Defined in Network.GRPC.Spec.CustomMetadata.NoMetadata

class ParseMetadata a where #

Methods

parseMetadata :: MonadThrow m => [CustomMetadata] -> m a #

Instances

Instances details
ParseMetadata NoMetadata 
Instance details

Defined in Network.GRPC.Spec.CustomMetadata.NoMetadata

class BuildMetadata a => StaticMetadata a where #

Instances

Instances details
StaticMetadata NoMetadata 
Instance details

Defined in Network.GRPC.Spec.CustomMetadata.NoMetadata

Configuration

data SslKeyLog Source #

SSL key log file

An SSL key log file can be used by tools such as Wireshark to decode TLS network traffic. It is used for debugging only.

Constructors

SslKeyLogNone

Don't use a key log file

SslKeyLogPath FilePath

Use the specified path

SslKeyLogFromEnv

Use the SSLKEYLOGFILE environment variable to determine the key log

This is the default.

Instances

Instances details
Default SslKeyLog Source # 
Instance details

Defined in Network.GRPC.Util.TLS

Methods

def :: SslKeyLog #

Generic SslKeyLog Source # 
Instance details

Defined in Network.GRPC.Util.TLS

Associated Types

type Rep SslKeyLog 
Instance details

Defined in Network.GRPC.Util.TLS

type Rep SslKeyLog = D1 ('MetaData "SslKeyLog" "Network.GRPC.Util.TLS" "grapesy-1.0.0-inplace" 'False) (C1 ('MetaCons "SslKeyLogNone" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SslKeyLogPath" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)) :+: C1 ('MetaCons "SslKeyLogFromEnv" 'PrefixI 'False) (U1 :: Type -> Type)))
Show SslKeyLog Source # 
Instance details

Defined in Network.GRPC.Util.TLS

Eq SslKeyLog Source # 
Instance details

Defined in Network.GRPC.Util.TLS

type Rep SslKeyLog Source # 
Instance details

Defined in Network.GRPC.Util.TLS

type Rep SslKeyLog = D1 ('MetaData "SslKeyLog" "Network.GRPC.Util.TLS" "grapesy-1.0.0-inplace" 'False) (C1 ('MetaCons "SslKeyLogNone" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SslKeyLogPath" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)) :+: C1 ('MetaCons "SslKeyLogFromEnv" 'PrefixI 'False) (U1 :: Type -> Type)))

HTTP/2 Settings

data HTTP2Settings Source #

HTTP/2 settings

Constructors

HTTP2Settings 

Fields

  • http2MaxConcurrentStreams :: Word32

    Maximum number of concurrent active streams

    https://datatracker.ietf.org/doc/html/rfc7540#section-5.1.2

  • http2StreamWindowSize :: Word32
  • http2ConnectionWindowSize :: Word32

    Connection window size

    This value is broadcast via a WINDOW_UDPATE frame at the beginning of a new connection.

    If the consumed window space of all streams exceeds this value, the sender will stop sending data. Therefore, if this value is less than http2MaxConcurrentStreams * http2StreamWindowSize, there is risk of a control flow deadlock, since the connection window space may be used up by streams that we are not yet processing before we have received all data on the streams that we are processing. To reduce this risk, increase serverOverrideNumberOfWorkers for the server. See https://github.com/kazu-yamamoto/network-control/pull/4 for more information.

  • http2TcpNoDelay :: Bool

    Enable TCP_NODELAY

    Send out TCP segments as soon as possible, even if there is only a small amount of data.

    When TCP_NODELAY is NOT set, the TCP implementation will wait to send a TCP segment to the receiving peer until either (1) there is enough data to fill a certain minimum segment size or (2) we receive an ACK from the receiving peer for data we sent previously. This adds a network roundtrip delay to every RPC message we want to send (to receive the ACK). If the peer uses TCP delayed acknowledgement, which will typically be the case, then this delay will increase further still; default for delayed acknowledgement is 40ms, thus resulting in a theoretical maximum of 25 RPCs/sec.

    We therefore enable TCP_NODELAY by default, so that data is sent to the peer as soon as we have an entire gRPC message serialized and ready to send (we send the data to the TCP layer only once an entire message is written, or the http2 write buffer is full).

    Turning this off could improve throughput, as fewer TCP segments will be needed, but you probably only want to do this if you send very few very large RPC messages. In gRPC this is anyway discouraged, because gRPC messages do not support incremental (de)serialization; if you need to send large amounts of data, it is preferable to split these into many, smaller, gRPC messages; this also gives the application the possibility of reporting on data transmission progress.

    TL;DR: leave this at the default unless you know what you are doing.

  • http2TcpAbortiveClose :: Bool

    Set SO_LINGER to a value of 0

    Instead of following the normal shutdown sequence to close the TCP connection, this will just send a RST packet and immediately discard the connection, freeing the local port.

    This should not be enabled in the vast majority of cases. It is only useful in specific scenarios, such as stress testing, where resource (e.g. port) exhaustion is a greater concern than protocol adherence. Even in such scenarios scenarios, it probably only makes sense to enable this option on the client since they will be using a new ephemeral port for each connection (unlike the server).

    TL;DR: leave this at the default unless you know what you are doing.

  • http2OverridePingRateLimit :: Maybe Int

    Ping rate limit

    This setting is specific to the http2 package's implementation of the HTTP/2 specification. In particular, the library imposes a ping rate limit as a security measure against CVE-2019-9512. By default (as of version 5.1.2) it sets this limit at 10 pings/second. If you find yourself being disconnected from a gRPC peer because that peer is sending too many pings (you will see an EnhanceYourCalm exception, corresponding to the ENHANCE_YOUR_CALM HTTP/2 error code), you may wish to increase this limit. If you are connecting to a peer that you trust, you can set this limit to maxBound (effectively turning off protection against ping flooding).

  • http2OverrideEmptyFrameRateLimit :: Maybe Int

    Empty DATA frame rate limit

    This setting is specific to the http2 package's implementation of the HTTP/2 specification. In particular, the library imposes a rate limit for empty DATA frames as a security measure against CVE-2019-9518. By default, it sets this limit at 4 frames/second. If you find yourself being disconnected from a gRPC peer because that peer is sending too many empty DATA frames (you will see an EnhanceYourCalm exception, corresponding to the ENHANCE_YOUR_CALM HTTP/2 error code), you may wish to increase this limit. If you are connecting to a peer that you trust, you can set this limit to maxBound (effectively turning off protection against empty DATA frame flooding).

  • http2OverrideSettingsRateLimit :: Maybe Int

    SETTINGS frame rate limit

    This setting is specific to the http2 package's implementation of the HTTP/2 specification. In particular, the library imposes a rate limit for SETTINGS frames as a security measure against CVE-2019-9515. By default, it sets this limit at 4 frames/second. If you find yourself being disconnected from a gRPC peer because that peer is sending too many SETTINGS frames (you will see an EnhanceYourCalm exception, corresponding to the ENHANCE_YOUR_CALM HTTP/2 error code), you may wish to increase this limit. If you are connecting to a peer that you trust, you can set this limit to maxBound (effectively turning off protection against SETTINGS frame flooding).

  • http2OverrideRstRateLimit :: Maybe Int

    Reset (RST) frame rate limit

    This setting is specific to the http2 package's implementation of the HTTP/2 specification. In particular, the library imposes a rate limit for RST frames as a security measure against CVE-2023-44487. By default, it sets this limit at 4 frames/second. If you find yourself being disconnected from a gRPC peer because that peer is sending too many empty RST frames (you will see an EnhanceYourCalm exception, corresponding to the ENHANCE_YOUR_CALM HTTP/2 error code), you may wish to increase this limit. If you are connecting to a peer that you trust, you can set this limit to maxBound (effectively turning off protection against RST frame flooding).

Instances

Instances details
Default HTTP2Settings Source # 
Instance details

Defined in Network.GRPC.Common.HTTP2Settings

Methods

def :: HTTP2Settings #

Show HTTP2Settings Source # 
Instance details

Defined in Network.GRPC.Common.HTTP2Settings

Defaults

defaultInsecurePort :: PortNumber Source #

Default port number for insecure servers

By convention, 50051 is often used as the default port for gRPC servers.

defaultSecurePort :: PortNumber Source #

Default port number for secure servers (50052)

Unlike defaultInsecurePort, this is a grapesy internal convention: we use 50052 as the defualt port for secure gRPC servers.

defaultHTTP2Settings :: HTTP2Settings Source #

Default HTTP/2 settings

Section 6.5.2 of the HTTP/2 specification recommends that the SETTINGS_MAX_CONCURRENT_STREAMS parameter be no smaller than 100 "so as not to unnecessarily limit parallelism", so we default to 128.

The default initial stream window size (corresponding to the SETTINGS_INITIAL_WINDOW_SIZE HTTP/2 parameter) is 64KB.

The default connection window size is 128 * 64KB to avoid the control flow deadlock discussed at http2ConnectionWindowSize.

The ping rate limit imposed by the http2 package is overridden to 100 PINGs/sec.

Message metadata

data OutboundMeta #

Instances

Instances details
Default OutboundMeta 
Instance details

Defined in Network.GRPC.Spec.MessageMeta

Methods

def :: OutboundMeta #

NFData OutboundMeta 
Instance details

Defined in Network.GRPC.Spec.MessageMeta

Methods

rnf :: OutboundMeta -> () #

Generic OutboundMeta 
Instance details

Defined in Network.GRPC.Spec.MessageMeta

Associated Types

type Rep OutboundMeta 
Instance details

Defined in Network.GRPC.Spec.MessageMeta

type Rep OutboundMeta = D1 ('MetaData "OutboundMeta" "Network.GRPC.Spec.MessageMeta" "grpc-spec-1.0.0-inplace" 'False) (C1 ('MetaCons "OutboundMeta" 'PrefixI 'True) (S1 ('MetaSel ('Just "outboundEnableCompression") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))
Show OutboundMeta 
Instance details

Defined in Network.GRPC.Spec.MessageMeta

type Rep OutboundMeta 
Instance details

Defined in Network.GRPC.Spec.MessageMeta

type Rep OutboundMeta = D1 ('MetaData "OutboundMeta" "Network.GRPC.Spec.MessageMeta" "grpc-spec-1.0.0-inplace" 'False) (C1 ('MetaCons "OutboundMeta" 'PrefixI 'True) (S1 ('MetaSel ('Just "outboundEnableCompression") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

data InboundMeta #

Instances

Instances details
Show InboundMeta 
Instance details

Defined in Network.GRPC.Spec.MessageMeta

Exceptions

gRPC status and exceptions

data GrpcStatus #

Constructors

GrpcOk 
GrpcError GrpcError 

Instances

Instances details
Generic GrpcStatus 
Instance details

Defined in Network.GRPC.Spec.Status

Associated Types

type Rep GrpcStatus 
Instance details

Defined in Network.GRPC.Spec.Status

type Rep GrpcStatus = D1 ('MetaData "GrpcStatus" "Network.GRPC.Spec.Status" "grpc-spec-1.0.0-inplace" 'False) (C1 ('MetaCons "GrpcOk" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GrpcError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GrpcError)))
Show GrpcStatus 
Instance details

Defined in Network.GRPC.Spec.Status

Eq GrpcStatus 
Instance details

Defined in Network.GRPC.Spec.Status

type Rep GrpcStatus 
Instance details

Defined in Network.GRPC.Spec.Status

type Rep GrpcStatus = D1 ('MetaData "GrpcStatus" "Network.GRPC.Spec.Status" "grpc-spec-1.0.0-inplace" 'False) (C1 ('MetaCons "GrpcOk" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GrpcError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GrpcError)))

data GrpcError #

Instances

Instances details
Exception GrpcError 
Instance details

Defined in Network.GRPC.Spec.Status

Generic GrpcError 
Instance details

Defined in Network.GRPC.Spec.Status

Associated Types

type Rep GrpcError 
Instance details

Defined in Network.GRPC.Spec.Status

type Rep GrpcError = D1 ('MetaData "GrpcError" "Network.GRPC.Spec.Status" "grpc-spec-1.0.0-inplace" 'False) ((((C1 ('MetaCons "GrpcCancelled" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GrpcUnknown" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GrpcInvalidArgument" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GrpcDeadlineExceeded" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "GrpcNotFound" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GrpcAlreadyExists" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GrpcPermissionDenied" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GrpcResourceExhausted" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "GrpcFailedPrecondition" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GrpcAborted" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GrpcOutOfRange" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GrpcUnimplemented" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "GrpcInternal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GrpcUnavailable" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GrpcDataLoss" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GrpcUnauthenticated" 'PrefixI 'False) (U1 :: Type -> Type)))))
Show GrpcError 
Instance details

Defined in Network.GRPC.Spec.Status

Eq GrpcError 
Instance details

Defined in Network.GRPC.Spec.Status

Ord GrpcError 
Instance details

Defined in Network.GRPC.Spec.Status

type Rep GrpcError 
Instance details

Defined in Network.GRPC.Spec.Status

type Rep GrpcError = D1 ('MetaData "GrpcError" "Network.GRPC.Spec.Status" "grpc-spec-1.0.0-inplace" 'False) ((((C1 ('MetaCons "GrpcCancelled" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GrpcUnknown" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GrpcInvalidArgument" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GrpcDeadlineExceeded" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "GrpcNotFound" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GrpcAlreadyExists" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GrpcPermissionDenied" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GrpcResourceExhausted" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "GrpcFailedPrecondition" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GrpcAborted" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GrpcOutOfRange" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GrpcUnimplemented" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "GrpcInternal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GrpcUnavailable" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GrpcDataLoss" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GrpcUnauthenticated" 'PrefixI 'False) (U1 :: Type -> Type)))))

Low-level

data ProtocolException (rpc :: k) Source #

Protocol exception

A protocol exception arises when the client and the server disagree on the sequence of inputs and outputs exchanged. This agreement might be part of a formal specification such as Protobuf, or it might be implicit in the implementation of a specific RPC.

Constructors

TooFewInputs

We expected an input but got none

TooManyInputs (Input rpc)

We received an input when we expected no more inputs

TooFewOutputs (ResponseTrailingMetadata rpc)

We expected an output, but got trailers instead

TooManyOutputs (Output rpc)

We expected trailers, but got an output instead

UnexpectedTrailersOnly (ResponseTrailingMetadata rpc)

The server unexpectedly used the Trailers-Only case

Instances

Instances details
IsRPC rpc => Show (ProtocolException rpc) Source # 
Instance details

Defined in Network.GRPC.Common

data ChannelDiscarded Source #

Channel was closed because it was discarded

This typically corresponds to leaving the scope of runHandler or withRPC (without throwing an exception).

data PeerException Source #

Misbehaving peer

Although this exception could in principle be caught, there is not much that can be done to rectify the situation: probably this peer should just be avoided (although perhaps one can hope that the problem was transient).

Constructors

PeerSentMalformedMessage String

Peer sent a malformed message (parser returned an error)

PeerSentIncompleteMessage

Peer sent an incomplete message (parser did not consume all data)

PeerMissingPseudoHeaderStatus

HTTP response missing :status pseudo-header

This is not part of CallSetupFailure because the call may have been well under way before the server initiates a response.

data SomeProtocolException where Source #

Existential wrapper around ProtocolException

This makes it easier to catch these exceptions (without this, you'd have to catch the exception for a specific instance of rpc).

Constructors

ProtocolException :: forall {k} (rpc :: k). IsRPC rpc => ProtocolException rpc -> SomeProtocolException 

newtype InvalidHeaders e #

Constructors

InvalidHeaders 

Instances

Instances details
Monoid (InvalidHeaders e) 
Instance details

Defined in Network.GRPC.Spec.Headers.Invalid

Semigroup (InvalidHeaders e) 
Instance details

Defined in Network.GRPC.Spec.Headers.Invalid

Show e => Show (InvalidHeaders e) 
Instance details

Defined in Network.GRPC.Spec.Headers.Invalid

Show e => Show (RequestHeaders' e) 
Instance details

Defined in Network.GRPC.Spec.Headers.Request

Methods

showsPrec :: Int -> RequestHeaders' e -> ShowS #

show :: RequestHeaders' e -> String #

showList :: [RequestHeaders' e] -> ShowS #

Eq e => Eq (InvalidHeaders e) 
Instance details

Defined in Network.GRPC.Spec.Headers.Invalid

Eq e => Eq (RequestHeaders' e) 
Instance details

Defined in Network.GRPC.Spec.Headers.Request

Methods

(==) :: RequestHeaders' e -> RequestHeaders' e -> Bool #

(/=) :: RequestHeaders' e -> RequestHeaders' e -> Bool #

User errors

data SendAfterFinal Source #

Thrown by send

The CallStack is the callstack of the final call to send.

See send for additional discussion.

Constructors

SendAfterFinal CallStack

Call to send after the final message was sent

SendButTrailersOnly

Call to send, but we are in the Trailers-Only case

data RecvAfterFinal Source #

Thrown by recv

The CallStack is the callstack of the final call to recv.

See recv for additional discussion.

Constructors

RecvAfterFinal CallStack

Call to recv after the final message was already received

Convenience re-exports

data Proxy (t :: k) #

Proxy is a type that holds no data, but has a phantom parameter of arbitrary type (or even kind). Its use is to provide type information, even though there is no value available of that type (or it may be too costly to create one).

Historically, Proxy :: Proxy a is a safer alternative to the undefined :: a idiom.

>>> Proxy :: Proxy (Void, Int -> Int)
Proxy

Proxy can even hold types of higher kinds,

>>> Proxy :: Proxy Either
Proxy
>>> Proxy :: Proxy Functor
Proxy
>>> Proxy :: Proxy complicatedStructure
Proxy

Constructors

Proxy 

Instances

Instances details
Generic1 (Proxy :: k -> Type) 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 (Proxy :: k -> Type)

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (Proxy :: k -> Type) = D1 ('MetaData "Proxy" "GHC.Internal.Data.Proxy" "ghc-internal" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: k -> Type))

Methods

from1 :: forall (a :: k). Proxy a -> Rep1 (Proxy :: k -> Type) a #

to1 :: forall (a :: k). Rep1 (Proxy :: k -> Type) a -> Proxy a #

Representable (Proxy :: Type -> Type) 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (Proxy :: Type -> Type) 
Instance details

Defined in Data.Functor.Rep

type Rep (Proxy :: Type -> Type) = Void

Methods

tabulate :: (Rep (Proxy :: Type -> Type) -> a) -> Proxy a #

index :: Proxy a -> Rep (Proxy :: Type -> Type) -> a #

FromJSON1 (Proxy :: Type -> Type) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

liftParseJSON :: Maybe a -> (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Proxy a) #

liftParseJSONList :: Maybe a -> (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Proxy a] #

liftOmittedField :: Maybe a -> Maybe (Proxy a) #

ToJSON1 (Proxy :: Type -> Type) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

liftToJSON :: (a -> Bool) -> (a -> Value) -> ([a] -> Value) -> Proxy a -> Value #

liftToJSONList :: (a -> Bool) -> (a -> Value) -> ([a] -> Value) -> [Proxy a] -> Value #

liftToEncoding :: (a -> Bool) -> (a -> Encoding) -> ([a] -> Encoding) -> Proxy a -> Encoding #

liftToEncodingList :: (a -> Bool) -> (a -> Encoding) -> ([a] -> Encoding) -> [Proxy a] -> Encoding #

liftOmitField :: (a -> Bool) -> Proxy a -> Bool #

MonadZip (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Zip

Methods

mzip :: Proxy a -> Proxy b -> Proxy (a, b) #

mzipWith :: (a -> b -> c) -> Proxy a -> Proxy b -> Proxy c #

munzip :: Proxy (a, b) -> (Proxy a, Proxy b) #

Eq1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> Proxy a -> Proxy b -> Bool #

Ord1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> Proxy a -> Proxy b -> Ordering #

Read1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Proxy a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Proxy a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Proxy a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Proxy a] #

Show1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Proxy a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Proxy a] -> ShowS #

Contravariant (Proxy :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> Proxy a -> Proxy a' #

(>$) :: b -> Proxy b -> Proxy a #

NFData1 (Proxy :: Type -> Type)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Proxy a -> () #

Alternative (Proxy :: Type -> Type)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

empty :: Proxy a #

(<|>) :: Proxy a -> Proxy a -> Proxy a #

some :: Proxy a -> Proxy [a] #

many :: Proxy a -> Proxy [a] #

Applicative (Proxy :: Type -> Type)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

pure :: a -> Proxy a #

(<*>) :: Proxy (a -> b) -> Proxy a -> Proxy b #

liftA2 :: (a -> b -> c) -> Proxy a -> Proxy b -> Proxy c #

(*>) :: Proxy a -> Proxy b -> Proxy b #

(<*) :: Proxy a -> Proxy b -> Proxy a #

Functor (Proxy :: Type -> Type)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

fmap :: (a -> b) -> Proxy a -> Proxy b #

(<$) :: a -> Proxy b -> Proxy a #

Monad (Proxy :: Type -> Type)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

(>>=) :: Proxy a -> (a -> Proxy b) -> Proxy b #

(>>) :: Proxy a -> Proxy b -> Proxy b #

return :: a -> Proxy a #

MonadPlus (Proxy :: Type -> Type)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

mzero :: Proxy a #

mplus :: Proxy a -> Proxy a -> Proxy a #

Foldable (Proxy :: Type -> Type)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Foldable

Methods

fold :: Monoid m => Proxy m -> m #

foldMap :: Monoid m => (a -> m) -> Proxy a -> m #

foldMap' :: Monoid m => (a -> m) -> Proxy a -> m #

foldr :: (a -> b -> b) -> b -> Proxy a -> b #

foldr' :: (a -> b -> b) -> b -> Proxy a -> b #

foldl :: (b -> a -> b) -> b -> Proxy a -> b #

foldl' :: (b -> a -> b) -> b -> Proxy a -> b #

foldr1 :: (a -> a -> a) -> Proxy a -> a #

foldl1 :: (a -> a -> a) -> Proxy a -> a #

toList :: Proxy a -> [a] #

null :: Proxy a -> Bool #

length :: Proxy a -> Int #

elem :: Eq a => a -> Proxy a -> Bool #

maximum :: Ord a => Proxy a -> a #

minimum :: Ord a => Proxy a -> a #

sum :: Num a => Proxy a -> a #

product :: Num a => Proxy a -> a #

Traversable (Proxy :: Type -> Type)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Proxy a -> f (Proxy b) #

sequenceA :: Applicative f => Proxy (f a) -> f (Proxy a) #

mapM :: Monad m => (a -> m b) -> Proxy a -> m (Proxy b) #

sequence :: Monad m => Proxy (m a) -> m (Proxy a) #

Hashable1 (Proxy :: Type -> Type) 
Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Proxy a -> Int #

FromJSON (Proxy a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

ToJSON (Proxy a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Default (Proxy a) 
Instance details

Defined in Data.Default.Internal

Methods

def :: Proxy a #

NFData (Proxy a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Proxy a -> () #

Monoid (Proxy s)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

mempty :: Proxy s #

mappend :: Proxy s -> Proxy s -> Proxy s #

mconcat :: [Proxy s] -> Proxy s #

Semigroup (Proxy s)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

(<>) :: Proxy s -> Proxy s -> Proxy s #

sconcat :: NonEmpty (Proxy s) -> Proxy s #

stimes :: Integral b => b -> Proxy s -> Proxy s #

Bounded (Proxy t)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

minBound :: Proxy t #

maxBound :: Proxy t #

Enum (Proxy s)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

succ :: Proxy s -> Proxy s #

pred :: Proxy s -> Proxy s #

toEnum :: Int -> Proxy s #

fromEnum :: Proxy s -> Int #

enumFrom :: Proxy s -> [Proxy s] #

enumFromThen :: Proxy s -> Proxy s -> [Proxy s] #

enumFromTo :: Proxy s -> Proxy s -> [Proxy s] #

enumFromThenTo :: Proxy s -> Proxy s -> Proxy s -> [Proxy s] #

Generic (Proxy t) 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep (Proxy t)

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep (Proxy t) = D1 ('MetaData "Proxy" "GHC.Internal.Data.Proxy" "ghc-internal" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: Proxy t -> Rep (Proxy t) x #

to :: Rep (Proxy t) x -> Proxy t #

Ix (Proxy s)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

range :: (Proxy s, Proxy s) -> [Proxy s] #

index :: (Proxy s, Proxy s) -> Proxy s -> Int #

unsafeIndex :: (Proxy s, Proxy s) -> Proxy s -> Int #

inRange :: (Proxy s, Proxy s) -> Proxy s -> Bool #

rangeSize :: (Proxy s, Proxy s) -> Int #

unsafeRangeSize :: (Proxy s, Proxy s) -> Int #

Read (Proxy t)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Show (Proxy s)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

showsPrec :: Int -> Proxy s -> ShowS #

show :: Proxy s -> String #

showList :: [Proxy s] -> ShowS #

Eq (Proxy s)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

(==) :: Proxy s -> Proxy s -> Bool #

(/=) :: Proxy s -> Proxy s -> Bool #

Ord (Proxy s)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

compare :: Proxy s -> Proxy s -> Ordering #

(<) :: Proxy s -> Proxy s -> Bool #

(<=) :: Proxy s -> Proxy s -> Bool #

(>) :: Proxy s -> Proxy s -> Bool #

(>=) :: Proxy s -> Proxy s -> Bool #

max :: Proxy s -> Proxy s -> Proxy s #

min :: Proxy s -> Proxy s -> Proxy s #

Hashable (Proxy a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Proxy a -> Int #

hash :: Proxy a -> Int #

type Rep1 (Proxy :: k -> Type)

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (Proxy :: k -> Type) = D1 ('MetaData "Proxy" "GHC.Internal.Data.Proxy" "ghc-internal" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: k -> Type))
type Rep (Proxy :: Type -> Type) 
Instance details

Defined in Data.Functor.Rep

type Rep (Proxy :: Type -> Type) = Void
type Rep (Proxy t)

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep (Proxy t) = D1 ('MetaData "Proxy" "GHC.Internal.Data.Proxy" "ghc-internal" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: Type -> Type))

class Default a where #

A class for types with a default value.

Minimal complete definition

Nothing

Methods

def :: a #

The default value for this type.

default def :: (Generic a, GDefault (Rep a)) => a #

Instances

Instances details
Default IntSet 
Instance details

Defined in Data.Default.Internal

Methods

def :: IntSet #

Default All 
Instance details

Defined in Data.Default.Internal

Methods

def :: All #

Default Any 
Instance details

Defined in Data.Default.Internal

Methods

def :: Any #

Default CBool 
Instance details

Defined in Data.Default.Internal

Methods

def :: CBool #

Default CClock 
Instance details

Defined in Data.Default.Internal

Methods

def :: CClock #

Default CDouble 
Instance details

Defined in Data.Default.Internal

Methods

def :: CDouble #

Default CFloat 
Instance details

Defined in Data.Default.Internal

Methods

def :: CFloat #

Default CInt 
Instance details

Defined in Data.Default.Internal

Methods

def :: CInt #

Default CIntMax 
Instance details

Defined in Data.Default.Internal

Methods

def :: CIntMax #

Default CIntPtr 
Instance details

Defined in Data.Default.Internal

Methods

def :: CIntPtr #

Default CLLong 
Instance details

Defined in Data.Default.Internal

Methods

def :: CLLong #

Default CLong 
Instance details

Defined in Data.Default.Internal

Methods

def :: CLong #

Default CPtrdiff 
Instance details

Defined in Data.Default.Internal

Methods

def :: CPtrdiff #

Default CSUSeconds 
Instance details

Defined in Data.Default.Internal

Methods

def :: CSUSeconds #

Default CShort 
Instance details

Defined in Data.Default.Internal

Methods

def :: CShort #

Default CSigAtomic 
Instance details

Defined in Data.Default.Internal

Methods

def :: CSigAtomic #

Default CSize 
Instance details

Defined in Data.Default.Internal

Methods

def :: CSize #

Default CTime 
Instance details

Defined in Data.Default.Internal

Methods

def :: CTime #

Default CUInt 
Instance details

Defined in Data.Default.Internal

Methods

def :: CUInt #

Default CUIntMax 
Instance details

Defined in Data.Default.Internal

Methods

def :: CUIntMax #

Default CUIntPtr 
Instance details

Defined in Data.Default.Internal

Methods

def :: CUIntPtr #

Default CULLong 
Instance details

Defined in Data.Default.Internal

Methods

def :: CULLong #

Default CULong 
Instance details

Defined in Data.Default.Internal

Methods

def :: CULong #

Default CUSeconds 
Instance details

Defined in Data.Default.Internal

Methods

def :: CUSeconds #

Default CUShort 
Instance details

Defined in Data.Default.Internal

Methods

def :: CUShort #

Default IntPtr 
Instance details

Defined in Data.Default.Internal

Methods

def :: IntPtr #

Default WordPtr 
Instance details

Defined in Data.Default.Internal

Methods

def :: WordPtr #

Default Int16 
Instance details

Defined in Data.Default.Internal

Methods

def :: Int16 #

Default Int32 
Instance details

Defined in Data.Default.Internal

Methods

def :: Int32 #

Default Int64 
Instance details

Defined in Data.Default.Internal

Methods

def :: Int64 #

Default Int8 
Instance details

Defined in Data.Default.Internal

Methods

def :: Int8 #

Default Word16 
Instance details

Defined in Data.Default.Internal

Methods

def :: Word16 #

Default Word32 
Instance details

Defined in Data.Default.Internal

Methods

def :: Word32 #

Default Word64 
Instance details

Defined in Data.Default.Internal

Methods

def :: Word64 #

Default Word8 
Instance details

Defined in Data.Default.Internal

Methods

def :: Word8 #

Default Ordering 
Instance details

Defined in Data.Default.Internal

Methods

def :: Ordering #

Default ConnParams Source # 
Instance details

Defined in Network.GRPC.Client.Connection

Methods

def :: ConnParams #

Default ReconnectPolicy Source #

The default policy is DontReconnect

The default follows the gRPC specification of Wait for Ready semantics https://github.com/grpc/grpc/blob/master/doc/wait-for-ready.md.

Instance details

Defined in Network.GRPC.Client.Connection

Default ReconnectTo Source # 
Instance details

Defined in Network.GRPC.Client.Connection

Methods

def :: ReconnectTo #

Default Negotation Source # 
Instance details

Defined in Network.GRPC.Common.Compression

Methods

def :: Negotation #

Default HTTP2Settings Source # 
Instance details

Defined in Network.GRPC.Common.HTTP2Settings

Methods

def :: HTTP2Settings #

Default ServerParams Source # 
Instance details

Defined in Network.GRPC.Server.Context

Methods

def :: ServerParams #

Default SslKeyLog Source # 
Instance details

Defined in Network.GRPC.Util.TLS

Methods

def :: SslKeyLog #

Default NoMetadata 
Instance details

Defined in Network.GRPC.Spec.CustomMetadata.NoMetadata

Methods

def :: NoMetadata #

Default ContentType 
Instance details

Defined in Network.GRPC.Spec.Headers.Common

Methods

def :: ContentType #

Default MessageType 
Instance details

Defined in Network.GRPC.Spec.Headers.Common

Methods

def :: MessageType #

Default OutboundMeta 
Instance details

Defined in Network.GRPC.Spec.MessageMeta

Methods

def :: OutboundMeta #

Default TraceContext 
Instance details

Defined in Network.GRPC.Spec.TraceContext

Methods

def :: TraceContext #

Default ClientHooks 
Instance details

Defined in Network.TLS.Parameters

Methods

def :: ClientHooks #

Default DebugParams 
Instance details

Defined in Network.TLS.Parameters

Methods

def :: DebugParams #

Default ServerHooks 
Instance details

Defined in Network.TLS.Parameters

Methods

def :: ServerHooks #

Default ServerParams 
Instance details

Defined in Network.TLS.Parameters

Methods

def :: ServerParams #

Default Shared 
Instance details

Defined in Network.TLS.Parameters

Methods

def :: Shared #

Default Supported 
Instance details

Defined in Network.TLS.Parameters

Methods

def :: Supported #

Default Integer 
Instance details

Defined in Data.Default.Internal

Methods

def :: Integer #

Default () 
Instance details

Defined in Data.Default.Internal

Methods

def :: () #

Default Bool 
Instance details

Defined in Data.Default.Internal

Methods

def :: Bool #

Default Double 
Instance details

Defined in Data.Default.Internal

Methods

def :: Double #

Default Float 
Instance details

Defined in Data.Default.Internal

Methods

def :: Float #

Default Int 
Instance details

Defined in Data.Default.Internal

Methods

def :: Int #

Default Word 
Instance details

Defined in Data.Default.Internal

Methods

def :: Word #

(Default a, RealFloat a) => Default (Complex a) 
Instance details

Defined in Data.Default.Internal

Methods

def :: Complex a #

Default (IntMap v) 
Instance details

Defined in Data.Default.Internal

Methods

def :: IntMap v #

Default (Seq a) 
Instance details

Defined in Data.Default.Internal

Methods

def :: Seq a #

Default (Set v) 
Instance details

Defined in Data.Default.Internal

Methods

def :: Set v #

Default a => Default (Tree a) 
Instance details

Defined in Data.Default.Internal

Methods

def :: Tree a #

Default a => Default (Identity a) 
Instance details

Defined in Data.Default.Internal

Methods

def :: Identity a #

Default (First a) 
Instance details

Defined in Data.Default.Internal

Methods

def :: First a #

Default (Last a) 
Instance details

Defined in Data.Default.Internal

Methods

def :: Last a #

Default a => Default (Dual a) 
Instance details

Defined in Data.Default.Internal

Methods

def :: Dual a #

Default (Endo a) 
Instance details

Defined in Data.Default.Internal

Methods

def :: Endo a #

Num a => Default (Product a) 
Instance details

Defined in Data.Default.Internal

Methods

def :: Product a #

Num a => Default (Sum a) 
Instance details

Defined in Data.Default.Internal

Methods

def :: Sum a #

Default (ConstPtr a) 
Instance details

Defined in Data.Default.Internal

Methods

def :: ConstPtr a #

Default (FunPtr a) 
Instance details

Defined in Data.Default.Internal

Methods

def :: FunPtr a #

Default (Ptr a) 
Instance details

Defined in Data.Default.Internal

Methods

def :: Ptr a #

Integral a => Default (Ratio a) 
Instance details

Defined in Data.Default.Internal

Methods

def :: Ratio a #

Default (Maybe a) 
Instance details

Defined in Data.Default.Internal

Methods

def :: Maybe a #

Default a => Default (Solo a) 
Instance details

Defined in Data.Default.Internal

Methods

def :: Solo a #

Default [a] 
Instance details

Defined in Data.Default.Internal

Methods

def :: [a] #

HasResolution a => Default (Fixed a) 
Instance details

Defined in Data.Default.Internal

Methods

def :: Fixed a #

Default (Map k v) 
Instance details

Defined in Data.Default.Internal

Methods

def :: Map k v #

Default (Proxy a) 
Instance details

Defined in Data.Default.Internal

Methods

def :: Proxy a #

Default (RequestMetadata rpc) => Default (CallParams rpc) 
Instance details

Defined in Network.GRPC.Spec.Call

Methods

def :: CallParams rpc #

(Default a1, Default a2) => Default (a1, a2) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2) #

Default a => Default (Const a b) 
Instance details

Defined in Data.Default.Internal

Methods

def :: Const a b #

(Default a1, Default a2, Default a3) => Default (a1, a2, a3) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2, a3) #

(Default a1, Default a2, Default a3, Default a4) => Default (a1, a2, a3, a4) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2, a3, a4) #

(Default a1, Default a2, Default a3, Default a4, Default a5) => Default (a1, a2, a3, a4, a5) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2, a3, a4, a5) #

(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6) => Default (a1, a2, a3, a4, a5, a6) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2, a3, a4, a5, a6) #

(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7) => Default (a1, a2, a3, a4, a5, a6, a7) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2, a3, a4, a5, a6, a7) #

(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8) => Default (a1, a2, a3, a4, a5, a6, a7, a8) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2, a3, a4, a5, a6, a7, a8) #

(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2, a3, a4, a5, a6, a7, a8, a9) #

(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) #

(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) #

(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) #

(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13) #

(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14) #

(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15) #

(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16) #

(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17) #

(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17, Default a18) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18) #

(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17, Default a18, Default a19) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19) #

(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17, Default a18, Default a19, Default a20) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20) #

(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17, Default a18, Default a19, Default a20, Default a21) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21) #

(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17, Default a18, Default a19, Default a20, Default a21, Default a22) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22) #

(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17, Default a18, Default a19, Default a20, Default a21, Default a22, Default a23) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23) #

(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17, Default a18, Default a19, Default a20, Default a21, Default a22, Default a23, Default a24) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24) #

(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17, Default a18, Default a19, Default a20, Default a21, Default a22, Default a23, Default a24, Default a25) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25) #

(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17, Default a18, Default a19, Default a20, Default a21, Default a22, Default a23, Default a24, Default a25, Default a26) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26) #

(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17, Default a18, Default a19, Default a20, Default a21, Default a22, Default a23, Default a24, Default a25, Default a26, Default a27) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27) #

(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17, Default a18, Default a19, Default a20, Default a21, Default a22, Default a23, Default a24, Default a25, Default a26, Default a27, Default a28) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28) #

(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17, Default a18, Default a19, Default a20, Default a21, Default a22, Default a23, Default a24, Default a25, Default a26, Default a27, Default a28, Default a29) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29) #

(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17, Default a18, Default a19, Default a20, Default a21, Default a22, Default a23, Default a24, Default a25, Default a26, Default a27, Default a28, Default a29, Default a30) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30) #

(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17, Default a18, Default a19, Default a20, Default a21, Default a22, Default a23, Default a24, Default a25, Default a26, Default a27, Default a28, Default a29, Default a30, Default a31) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31) 
Instance details

Defined in Data.Default.Internal

Methods

def :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31) #