module ClickHaskell.Packets where
import ClickHaskell.Primitive
import GHC.Generics
import Data.Int
data DataPacket = MkDataPacket
{ DataPacket -> ChString
table_name :: ChString
, DataPacket -> BlockInfo
block_info :: BlockInfo
, DataPacket -> UVarInt
columns_count :: UVarInt
, DataPacket -> UVarInt
rows_count :: UVarInt
}
deriving ((forall x. DataPacket -> Rep DataPacket x)
-> (forall x. Rep DataPacket x -> DataPacket) -> Generic DataPacket
forall x. Rep DataPacket x -> DataPacket
forall x. DataPacket -> Rep DataPacket x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DataPacket -> Rep DataPacket x
from :: forall x. DataPacket -> Rep DataPacket x
$cto :: forall x. Rep DataPacket x -> DataPacket
to :: forall x. Rep DataPacket x -> DataPacket
Generic, ProtocolRevision -> DataPacket -> Builder
(ProtocolRevision -> DataPacket -> Builder)
-> Serializable DataPacket
forall chType.
(ProtocolRevision -> chType -> Builder) -> Serializable chType
$cserialize :: ProtocolRevision -> DataPacket -> Builder
serialize :: ProtocolRevision -> DataPacket -> Builder
Serializable, ProtocolRevision -> Get DataPacket
(ProtocolRevision -> Get DataPacket) -> Deserializable DataPacket
forall chType.
(ProtocolRevision -> Get chType) -> Deserializable chType
$cdeserialize :: ProtocolRevision -> Get DataPacket
deserialize :: ProtocolRevision -> Get DataPacket
Deserializable)
data BlockInfo = MkBlockInfo
{ BlockInfo -> UVarInt
field_num1 :: UVarInt, BlockInfo -> UInt8
is_overflows :: UInt8
, BlockInfo -> UVarInt
field_num2 :: UVarInt, BlockInfo -> Int32
bucket_num :: Int32
, BlockInfo -> UVarInt
eof :: UVarInt
}
deriving ((forall x. BlockInfo -> Rep BlockInfo x)
-> (forall x. Rep BlockInfo x -> BlockInfo) -> Generic BlockInfo
forall x. Rep BlockInfo x -> BlockInfo
forall x. BlockInfo -> Rep BlockInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BlockInfo -> Rep BlockInfo x
from :: forall x. BlockInfo -> Rep BlockInfo x
$cto :: forall x. Rep BlockInfo x -> BlockInfo
to :: forall x. Rep BlockInfo x -> BlockInfo
Generic, ProtocolRevision -> BlockInfo -> Builder
(ProtocolRevision -> BlockInfo -> Builder)
-> Serializable BlockInfo
forall chType.
(ProtocolRevision -> chType -> Builder) -> Serializable chType
$cserialize :: ProtocolRevision -> BlockInfo -> Builder
serialize :: ProtocolRevision -> BlockInfo -> Builder
Serializable, ProtocolRevision -> Get BlockInfo
(ProtocolRevision -> Get BlockInfo) -> Deserializable BlockInfo
forall chType.
(ProtocolRevision -> Get chType) -> Deserializable chType
$cdeserialize :: ProtocolRevision -> Get BlockInfo
deserialize :: ProtocolRevision -> Get BlockInfo
Deserializable)
data ServerPacket where
HelloResponse :: HelloResponse -> ServerPacket
DataResponse :: DataPacket -> ServerPacket
Exception :: ExceptionPacket -> ServerPacket
Progress :: ProgressPacket -> ServerPacket
Pong :: ServerPacket
EndOfStream :: ServerPacket
ProfileInfo :: ProfileInfo -> ServerPacket
Totals :: ServerPacket
Extremes :: ServerPacket
TablesStatusResponse :: ServerPacket
Log :: ServerPacket
TableColumns :: TableColumns -> ServerPacket
UUIDs :: ServerPacket
ReadTaskRequest :: ServerPacket
ProfileEvents :: ServerPacket
UnknownPacket :: UVarInt -> ServerPacket
instance Deserializable ServerPacket where
deserialize :: ProtocolRevision -> Get ServerPacket
deserialize ProtocolRevision
rev = do
UVarInt
packetNum <- forall chType.
Deserializable chType =>
ProtocolRevision -> Get chType
deserialize @UVarInt ProtocolRevision
rev
case UVarInt
packetNum of
UVarInt
0 -> HelloResponse -> ServerPacket
HelloResponse (HelloResponse -> ServerPacket)
-> Get HelloResponse -> Get ServerPacket
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ProtocolRevision -> Get HelloResponse
forall chType.
Deserializable chType =>
ProtocolRevision -> Get chType
deserialize ProtocolRevision
rev
UVarInt
1 -> DataPacket -> ServerPacket
DataResponse (DataPacket -> ServerPacket) -> Get DataPacket -> Get ServerPacket
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ProtocolRevision -> Get DataPacket
forall chType.
Deserializable chType =>
ProtocolRevision -> Get chType
deserialize ProtocolRevision
rev
UVarInt
2 -> ExceptionPacket -> ServerPacket
Exception (ExceptionPacket -> ServerPacket)
-> Get ExceptionPacket -> Get ServerPacket
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ProtocolRevision -> Get ExceptionPacket
forall chType.
Deserializable chType =>
ProtocolRevision -> Get chType
deserialize ProtocolRevision
rev
UVarInt
3 -> ProgressPacket -> ServerPacket
Progress (ProgressPacket -> ServerPacket)
-> Get ProgressPacket -> Get ServerPacket
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ProtocolRevision -> Get ProgressPacket
forall chType.
Deserializable chType =>
ProtocolRevision -> Get chType
deserialize ProtocolRevision
rev
UVarInt
4 -> ServerPacket -> Get ServerPacket
forall a. a -> Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ServerPacket
Pong
UVarInt
5 -> ServerPacket -> Get ServerPacket
forall a. a -> Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ServerPacket
EndOfStream
UVarInt
6 -> ProfileInfo -> ServerPacket
ProfileInfo (ProfileInfo -> ServerPacket)
-> Get ProfileInfo -> Get ServerPacket
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ProtocolRevision -> Get ProfileInfo
forall chType.
Deserializable chType =>
ProtocolRevision -> Get chType
deserialize ProtocolRevision
rev
UVarInt
7 -> ServerPacket -> Get ServerPacket
forall a. a -> Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ServerPacket
Totals
UVarInt
8 -> ServerPacket -> Get ServerPacket
forall a. a -> Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ServerPacket
Extremes
UVarInt
9 -> ServerPacket -> Get ServerPacket
forall a. a -> Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ServerPacket
TablesStatusResponse
UVarInt
10 -> ServerPacket -> Get ServerPacket
forall a. a -> Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ServerPacket
Log
UVarInt
11 -> TableColumns -> ServerPacket
TableColumns (TableColumns -> ServerPacket)
-> Get TableColumns -> Get ServerPacket
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ProtocolRevision -> Get TableColumns
forall chType.
Deserializable chType =>
ProtocolRevision -> Get chType
deserialize ProtocolRevision
rev
UVarInt
12 -> ServerPacket -> Get ServerPacket
forall a. a -> Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ServerPacket
UUIDs
UVarInt
13 -> ServerPacket -> Get ServerPacket
forall a. a -> Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ServerPacket
ReadTaskRequest
UVarInt
14 -> ServerPacket -> Get ServerPacket
forall a. a -> Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ServerPacket
ProfileEvents
UVarInt
_ -> ServerPacket -> Get ServerPacket
forall a. a -> Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ServerPacket -> Get ServerPacket)
-> ServerPacket -> Get ServerPacket
forall a b. (a -> b) -> a -> b
$ UVarInt -> ServerPacket
UnknownPacket UVarInt
packetNum
serverPacketToNum :: ServerPacket -> UVarInt
serverPacketToNum :: ServerPacket -> UVarInt
serverPacketToNum = \case
(HelloResponse HelloResponse
_) -> UVarInt
0; (DataResponse DataPacket
_) -> UVarInt
1
(Exception ExceptionPacket
_) -> UVarInt
2; (Progress ProgressPacket
_) -> UVarInt
3;
(ServerPacket
Pong) -> UVarInt
4; (ServerPacket
EndOfStream) -> UVarInt
5
(ProfileInfo ProfileInfo
_) -> UVarInt
6; (ServerPacket
Totals) -> UVarInt
7
(ServerPacket
Extremes) -> UVarInt
8; (ServerPacket
TablesStatusResponse) -> UVarInt
9
(ServerPacket
Log) -> UVarInt
10; (TableColumns TableColumns
_) -> UVarInt
11;
(ServerPacket
UUIDs) -> UVarInt
12; (ServerPacket
ReadTaskRequest) -> UVarInt
13
(ServerPacket
ProfileEvents) -> UVarInt
14; (UnknownPacket UVarInt
num) -> UVarInt
num
data HelloResponse = MkHelloResponse
{ HelloResponse -> ChString
server_name :: ChString
, HelloResponse -> UVarInt
server_version_major :: UVarInt
, HelloResponse -> UVarInt
server_version_minor :: UVarInt
, HelloResponse -> ProtocolRevision
server_revision :: ProtocolRevision
, HelloResponse
-> SinceRevision
UVarInt DBMS_MIN_REVISION_WITH_VERSIONED_PARALLEL_REPLICAS_PROTOCOL
server_parallel_replicas_proto :: UVarInt `SinceRevision` DBMS_MIN_REVISION_WITH_VERSIONED_PARALLEL_REPLICAS_PROTOCOL
, HelloResponse
-> SinceRevision ChString DBMS_MIN_REVISION_WITH_SERVER_TIMEZONE
server_timezone :: ChString `SinceRevision` DBMS_MIN_REVISION_WITH_SERVER_TIMEZONE
, HelloResponse
-> SinceRevision
ChString DBMS_MIN_REVISION_WITH_SERVER_DISPLAY_NAME
server_display_name :: ChString `SinceRevision` DBMS_MIN_REVISION_WITH_SERVER_DISPLAY_NAME
, HelloResponse
-> SinceRevision UVarInt DBMS_MIN_REVISION_WITH_VERSION_PATCH
server_version_patch :: UVarInt `SinceRevision` DBMS_MIN_REVISION_WITH_VERSION_PATCH
, HelloResponse
-> SinceRevision
ChString DBMS_MIN_PROTOCOL_VERSION_WITH_CHUNKED_PACKETS
proto_send_chunked_srv :: ChString `SinceRevision` DBMS_MIN_PROTOCOL_VERSION_WITH_CHUNKED_PACKETS
, HelloResponse
-> SinceRevision
ChString DBMS_MIN_PROTOCOL_VERSION_WITH_CHUNKED_PACKETS
proto_recv_chunked_srv :: ChString `SinceRevision` DBMS_MIN_PROTOCOL_VERSION_WITH_CHUNKED_PACKETS
, HelloResponse
-> SinceRevision
[PasswordComplexityRules]
DBMS_MIN_PROTOCOL_VERSION_WITH_PASSWORD_COMPLEXITY_RULES
password_complexity_rules :: [PasswordComplexityRules] `SinceRevision` DBMS_MIN_PROTOCOL_VERSION_WITH_PASSWORD_COMPLEXITY_RULES
, HelloResponse
-> SinceRevision
UInt64 DBMS_MIN_REVISION_WITH_INTERSERVER_SECRET_V2
read_nonce :: UInt64 `SinceRevision` DBMS_MIN_REVISION_WITH_INTERSERVER_SECRET_V2
}
deriving ((forall x. HelloResponse -> Rep HelloResponse x)
-> (forall x. Rep HelloResponse x -> HelloResponse)
-> Generic HelloResponse
forall x. Rep HelloResponse x -> HelloResponse
forall x. HelloResponse -> Rep HelloResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. HelloResponse -> Rep HelloResponse x
from :: forall x. HelloResponse -> Rep HelloResponse x
$cto :: forall x. Rep HelloResponse x -> HelloResponse
to :: forall x. Rep HelloResponse x -> HelloResponse
Generic, ProtocolRevision -> Get HelloResponse
(ProtocolRevision -> Get HelloResponse)
-> Deserializable HelloResponse
forall chType.
(ProtocolRevision -> Get chType) -> Deserializable chType
$cdeserialize :: ProtocolRevision -> Get HelloResponse
deserialize :: ProtocolRevision -> Get HelloResponse
Deserializable)
data PasswordComplexityRules = MkPasswordComplexityRules
{ PasswordComplexityRules -> ChString
original_pattern :: ChString
, PasswordComplexityRules -> ChString
exception_message :: ChString
}
deriving ((forall x.
PasswordComplexityRules -> Rep PasswordComplexityRules x)
-> (forall x.
Rep PasswordComplexityRules x -> PasswordComplexityRules)
-> Generic PasswordComplexityRules
forall x. Rep PasswordComplexityRules x -> PasswordComplexityRules
forall x. PasswordComplexityRules -> Rep PasswordComplexityRules x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PasswordComplexityRules -> Rep PasswordComplexityRules x
from :: forall x. PasswordComplexityRules -> Rep PasswordComplexityRules x
$cto :: forall x. Rep PasswordComplexityRules x -> PasswordComplexityRules
to :: forall x. Rep PasswordComplexityRules x -> PasswordComplexityRules
Generic, ProtocolRevision -> Get PasswordComplexityRules
(ProtocolRevision -> Get PasswordComplexityRules)
-> Deserializable PasswordComplexityRules
forall chType.
(ProtocolRevision -> Get chType) -> Deserializable chType
$cdeserialize :: ProtocolRevision -> Get PasswordComplexityRules
deserialize :: ProtocolRevision -> Get PasswordComplexityRules
Deserializable)
data ExceptionPacket = MkExceptionPacket
{ ExceptionPacket -> Int32
code :: Int32
, ExceptionPacket -> ChString
name :: ChString
, ExceptionPacket -> ChString
message :: ChString
, ExceptionPacket -> ChString
stack_trace :: ChString
, ExceptionPacket -> UInt8
nested :: UInt8
}
deriving ((forall x. ExceptionPacket -> Rep ExceptionPacket x)
-> (forall x. Rep ExceptionPacket x -> ExceptionPacket)
-> Generic ExceptionPacket
forall x. Rep ExceptionPacket x -> ExceptionPacket
forall x. ExceptionPacket -> Rep ExceptionPacket x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ExceptionPacket -> Rep ExceptionPacket x
from :: forall x. ExceptionPacket -> Rep ExceptionPacket x
$cto :: forall x. Rep ExceptionPacket x -> ExceptionPacket
to :: forall x. Rep ExceptionPacket x -> ExceptionPacket
Generic, Int -> ExceptionPacket -> ShowS
[ExceptionPacket] -> ShowS
ExceptionPacket -> String
(Int -> ExceptionPacket -> ShowS)
-> (ExceptionPacket -> String)
-> ([ExceptionPacket] -> ShowS)
-> Show ExceptionPacket
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExceptionPacket -> ShowS
showsPrec :: Int -> ExceptionPacket -> ShowS
$cshow :: ExceptionPacket -> String
show :: ExceptionPacket -> String
$cshowList :: [ExceptionPacket] -> ShowS
showList :: [ExceptionPacket] -> ShowS
Show, ProtocolRevision -> Get ExceptionPacket
(ProtocolRevision -> Get ExceptionPacket)
-> Deserializable ExceptionPacket
forall chType.
(ProtocolRevision -> Get chType) -> Deserializable chType
$cdeserialize :: ProtocolRevision -> Get ExceptionPacket
deserialize :: ProtocolRevision -> Get ExceptionPacket
Deserializable)
data ProgressPacket = MkProgressPacket
{ ProgressPacket -> UVarInt
rows :: UVarInt
, ProgressPacket -> UVarInt
bytes :: UVarInt
, ProgressPacket -> UVarInt
total_rows :: UVarInt
, ProgressPacket
-> SinceRevision
UVarInt DBMS_MIN_PROTOCOL_VERSION_WITH_TOTAL_BYTES_IN_PROGRESS
total_bytes :: UVarInt `SinceRevision` DBMS_MIN_PROTOCOL_VERSION_WITH_TOTAL_BYTES_IN_PROGRESS
, ProgressPacket
-> SinceRevision
UVarInt DBMS_MIN_PROTOCOL_VERSION_WITH_TOTAL_BYTES_IN_PROGRESS
wrote_rows :: UVarInt `SinceRevision` DBMS_MIN_PROTOCOL_VERSION_WITH_TOTAL_BYTES_IN_PROGRESS
, ProgressPacket
-> SinceRevision UVarInt DBMS_MIN_REVISION_WITH_CLIENT_WRITE_INFO
wrote_bytes :: UVarInt `SinceRevision` DBMS_MIN_REVISION_WITH_CLIENT_WRITE_INFO
, ProgressPacket
-> SinceRevision UVarInt DBMS_MIN_REVISION_WITH_CLIENT_WRITE_INFO
elapsed_ns :: UVarInt `SinceRevision` DBMS_MIN_REVISION_WITH_CLIENT_WRITE_INFO
}
deriving ((forall x. ProgressPacket -> Rep ProgressPacket x)
-> (forall x. Rep ProgressPacket x -> ProgressPacket)
-> Generic ProgressPacket
forall x. Rep ProgressPacket x -> ProgressPacket
forall x. ProgressPacket -> Rep ProgressPacket x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ProgressPacket -> Rep ProgressPacket x
from :: forall x. ProgressPacket -> Rep ProgressPacket x
$cto :: forall x. Rep ProgressPacket x -> ProgressPacket
to :: forall x. Rep ProgressPacket x -> ProgressPacket
Generic, ProtocolRevision -> Get ProgressPacket
(ProtocolRevision -> Get ProgressPacket)
-> Deserializable ProgressPacket
forall chType.
(ProtocolRevision -> Get chType) -> Deserializable chType
$cdeserialize :: ProtocolRevision -> Get ProgressPacket
deserialize :: ProtocolRevision -> Get ProgressPacket
Deserializable)
data ProfileInfo = MkProfileInfo
{ ProfileInfo -> UVarInt
rows :: UVarInt
, ProfileInfo -> UVarInt
blocks :: UVarInt
, ProfileInfo -> UVarInt
bytes :: UVarInt
, ProfileInfo -> UInt8
applied_limit :: UInt8
, ProfileInfo -> UVarInt
rows_before_limit :: UVarInt
, ProfileInfo -> UInt8
calculated_rows_before_limit :: UInt8
, ProfileInfo
-> SinceRevision
UInt8 DBMS_MIN_REVISION_WITH_ROWS_BEFORE_AGGREGATION
applied_aggregation :: UInt8 `SinceRevision` DBMS_MIN_REVISION_WITH_ROWS_BEFORE_AGGREGATION
, ProfileInfo
-> SinceRevision
UVarInt DBMS_MIN_REVISION_WITH_ROWS_BEFORE_AGGREGATION
rows_before_aggregation :: UVarInt `SinceRevision` DBMS_MIN_REVISION_WITH_ROWS_BEFORE_AGGREGATION
}
deriving ((forall x. ProfileInfo -> Rep ProfileInfo x)
-> (forall x. Rep ProfileInfo x -> ProfileInfo)
-> Generic ProfileInfo
forall x. Rep ProfileInfo x -> ProfileInfo
forall x. ProfileInfo -> Rep ProfileInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ProfileInfo -> Rep ProfileInfo x
from :: forall x. ProfileInfo -> Rep ProfileInfo x
$cto :: forall x. Rep ProfileInfo x -> ProfileInfo
to :: forall x. Rep ProfileInfo x -> ProfileInfo
Generic, ProtocolRevision -> Get ProfileInfo
(ProtocolRevision -> Get ProfileInfo) -> Deserializable ProfileInfo
forall chType.
(ProtocolRevision -> Get chType) -> Deserializable chType
$cdeserialize :: ProtocolRevision -> Get ProfileInfo
deserialize :: ProtocolRevision -> Get ProfileInfo
Deserializable)
data TableColumns = MkTableColumns
{ TableColumns -> ChString
table_name :: ChString
, TableColumns -> ChString
table_columns :: ChString
}
deriving ((forall x. TableColumns -> Rep TableColumns x)
-> (forall x. Rep TableColumns x -> TableColumns)
-> Generic TableColumns
forall x. Rep TableColumns x -> TableColumns
forall x. TableColumns -> Rep TableColumns x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TableColumns -> Rep TableColumns x
from :: forall x. TableColumns -> Rep TableColumns x
$cto :: forall x. Rep TableColumns x -> TableColumns
to :: forall x. Rep TableColumns x -> TableColumns
Generic, ProtocolRevision -> Get TableColumns
(ProtocolRevision -> Get TableColumns)
-> Deserializable TableColumns
forall chType.
(ProtocolRevision -> Get chType) -> Deserializable chType
$cdeserialize :: ProtocolRevision -> Get TableColumns
deserialize :: ProtocolRevision -> Get TableColumns
Deserializable)
data ClientPacket where
Hello :: HelloPacket -> ClientPacket
Query :: QueryPacket -> ClientPacket
Data :: DataPacket -> ClientPacket
Cancel :: ClientPacket
Ping :: ClientPacket
TablesStatusRequest :: ClientPacket
KeepAlive :: ClientPacket
Scalar :: ClientPacket
IgnoredPartUUIDs :: ClientPacket
ReadTaskResponse :: ClientPacket
MergeTreeReadTaskResponse :: ClientPacket
SSHChallengeRequest :: ClientPacket
SSHChallengeResponse :: ClientPacket
deriving ((forall x. ClientPacket -> Rep ClientPacket x)
-> (forall x. Rep ClientPacket x -> ClientPacket)
-> Generic ClientPacket
forall x. Rep ClientPacket x -> ClientPacket
forall x. ClientPacket -> Rep ClientPacket x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ClientPacket -> Rep ClientPacket x
from :: forall x. ClientPacket -> Rep ClientPacket x
$cto :: forall x. Rep ClientPacket x -> ClientPacket
to :: forall x. Rep ClientPacket x -> ClientPacket
Generic)
instance Serializable ClientPacket where
serialize :: ProtocolRevision -> ClientPacket -> Builder
serialize ProtocolRevision
rev ClientPacket
packet = case ClientPacket
packet of
(Hello HelloPacket
p) -> forall chType.
Serializable chType =>
ProtocolRevision -> chType -> Builder
serialize @UVarInt ProtocolRevision
rev UVarInt
0 Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> ProtocolRevision -> HelloPacket -> Builder
forall chType.
Serializable chType =>
ProtocolRevision -> chType -> Builder
serialize ProtocolRevision
rev HelloPacket
p
(Query QueryPacket
p) -> forall chType.
Serializable chType =>
ProtocolRevision -> chType -> Builder
serialize @UVarInt ProtocolRevision
rev UVarInt
1 Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> ProtocolRevision -> QueryPacket -> Builder
forall chType.
Serializable chType =>
ProtocolRevision -> chType -> Builder
serialize ProtocolRevision
rev QueryPacket
p
(Data DataPacket
p) -> forall chType.
Serializable chType =>
ProtocolRevision -> chType -> Builder
serialize @UVarInt ProtocolRevision
rev UVarInt
2 Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> ProtocolRevision -> DataPacket -> Builder
forall chType.
Serializable chType =>
ProtocolRevision -> chType -> Builder
serialize ProtocolRevision
rev DataPacket
p
(ClientPacket
Cancel) -> forall chType.
Serializable chType =>
ProtocolRevision -> chType -> Builder
serialize @UVarInt ProtocolRevision
rev UVarInt
3
(ClientPacket
Ping) -> forall chType.
Serializable chType =>
ProtocolRevision -> chType -> Builder
serialize @UVarInt ProtocolRevision
rev UVarInt
4
(ClientPacket
TablesStatusRequest) -> forall chType.
Serializable chType =>
ProtocolRevision -> chType -> Builder
serialize @UVarInt ProtocolRevision
rev UVarInt
5
(ClientPacket
KeepAlive) -> forall chType.
Serializable chType =>
ProtocolRevision -> chType -> Builder
serialize @UVarInt ProtocolRevision
rev UVarInt
6
(ClientPacket
Scalar) -> forall chType.
Serializable chType =>
ProtocolRevision -> chType -> Builder
serialize @UVarInt ProtocolRevision
rev UVarInt
7
(ClientPacket
IgnoredPartUUIDs) -> forall chType.
Serializable chType =>
ProtocolRevision -> chType -> Builder
serialize @UVarInt ProtocolRevision
rev UVarInt
8
(ClientPacket
ReadTaskResponse) -> forall chType.
Serializable chType =>
ProtocolRevision -> chType -> Builder
serialize @UVarInt ProtocolRevision
rev UVarInt
9
(ClientPacket
MergeTreeReadTaskResponse) -> forall chType.
Serializable chType =>
ProtocolRevision -> chType -> Builder
serialize @UVarInt ProtocolRevision
rev UVarInt
10
(ClientPacket
SSHChallengeRequest) -> forall chType.
Serializable chType =>
ProtocolRevision -> chType -> Builder
serialize @UVarInt ProtocolRevision
rev UVarInt
11
(ClientPacket
SSHChallengeResponse) -> forall chType.
Serializable chType =>
ProtocolRevision -> chType -> Builder
serialize @UVarInt ProtocolRevision
rev UVarInt
12
data HelloPacket = MkHelloPacket
{ HelloPacket -> ChString
client_name :: ChString
, HelloPacket -> UVarInt
client_version_major :: UVarInt
, HelloPacket -> UVarInt
client_version_minor :: UVarInt
, HelloPacket -> ProtocolRevision
tcp_protocol_version :: ProtocolRevision
, HelloPacket -> ChString
default_database :: ChString
, HelloPacket -> ChString
user :: ChString
, HelloPacket -> ChString
pass :: ChString
}
deriving ((forall x. HelloPacket -> Rep HelloPacket x)
-> (forall x. Rep HelloPacket x -> HelloPacket)
-> Generic HelloPacket
forall x. Rep HelloPacket x -> HelloPacket
forall x. HelloPacket -> Rep HelloPacket x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. HelloPacket -> Rep HelloPacket x
from :: forall x. HelloPacket -> Rep HelloPacket x
$cto :: forall x. Rep HelloPacket x -> HelloPacket
to :: forall x. Rep HelloPacket x -> HelloPacket
Generic, ProtocolRevision -> HelloPacket -> Builder
(ProtocolRevision -> HelloPacket -> Builder)
-> Serializable HelloPacket
forall chType.
(ProtocolRevision -> chType -> Builder) -> Serializable chType
$cserialize :: ProtocolRevision -> HelloPacket -> Builder
serialize :: ProtocolRevision -> HelloPacket -> Builder
Serializable)
data Addendum = MkAddendum{Addendum
-> SinceRevision ChString DBMS_MIN_PROTOCOL_VERSION_WITH_QUOTA_KEY
quota_key :: ChString `SinceRevision` DBMS_MIN_PROTOCOL_VERSION_WITH_QUOTA_KEY}
deriving ((forall x. Addendum -> Rep Addendum x)
-> (forall x. Rep Addendum x -> Addendum) -> Generic Addendum
forall x. Rep Addendum x -> Addendum
forall x. Addendum -> Rep Addendum x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Addendum -> Rep Addendum x
from :: forall x. Addendum -> Rep Addendum x
$cto :: forall x. Rep Addendum x -> Addendum
to :: forall x. Rep Addendum x -> Addendum
Generic, ProtocolRevision -> Addendum -> Builder
(ProtocolRevision -> Addendum -> Builder) -> Serializable Addendum
forall chType.
(ProtocolRevision -> chType -> Builder) -> Serializable chType
$cserialize :: ProtocolRevision -> Addendum -> Builder
serialize :: ProtocolRevision -> Addendum -> Builder
Serializable)
data QueryPacket = MkQueryPacket
{ QueryPacket -> ChString
query_id :: ChString
, QueryPacket
-> SinceRevision ClientInfo DBMS_MIN_REVISION_WITH_CLIENT_INFO
client_info :: ClientInfo `SinceRevision` DBMS_MIN_REVISION_WITH_CLIENT_INFO
, QueryPacket -> DbSettings
settings :: DbSettings
, QueryPacket
-> SinceRevision ChString DBMS_MIN_REVISION_WITH_INTERSERVER_SECRET
interserver_secret :: ChString `SinceRevision` DBMS_MIN_REVISION_WITH_INTERSERVER_SECRET
, QueryPacket -> QueryStage
query_stage :: QueryStage
, QueryPacket -> UVarInt
compression :: UVarInt
, QueryPacket -> ChString
query :: ChString
, QueryPacket
-> SinceRevision
QueryParameters DBMS_MIN_PROTOCOL_VERSION_WITH_PARAMETERS
parameters :: QueryParameters `SinceRevision` DBMS_MIN_PROTOCOL_VERSION_WITH_PARAMETERS
}
deriving ((forall x. QueryPacket -> Rep QueryPacket x)
-> (forall x. Rep QueryPacket x -> QueryPacket)
-> Generic QueryPacket
forall x. Rep QueryPacket x -> QueryPacket
forall x. QueryPacket -> Rep QueryPacket x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. QueryPacket -> Rep QueryPacket x
from :: forall x. QueryPacket -> Rep QueryPacket x
$cto :: forall x. Rep QueryPacket x -> QueryPacket
to :: forall x. Rep QueryPacket x -> QueryPacket
Generic, ProtocolRevision -> QueryPacket -> Builder
(ProtocolRevision -> QueryPacket -> Builder)
-> Serializable QueryPacket
forall chType.
(ProtocolRevision -> chType -> Builder) -> Serializable chType
$cserialize :: ProtocolRevision -> QueryPacket -> Builder
serialize :: ProtocolRevision -> QueryPacket -> Builder
Serializable)
data DbSettings = MkDbSettings
instance Serializable DbSettings where serialize :: ProtocolRevision -> DbSettings -> Builder
serialize ProtocolRevision
rev DbSettings
_ = forall chType.
Serializable chType =>
ProtocolRevision -> chType -> Builder
serialize @ChString ProtocolRevision
rev ChString
""
data QueryParameters = MkQueryParameters
instance Serializable QueryParameters where serialize :: ProtocolRevision -> QueryParameters -> Builder
serialize ProtocolRevision
rev QueryParameters
_ = forall chType.
Serializable chType =>
ProtocolRevision -> chType -> Builder
serialize @ChString ProtocolRevision
rev ChString
""
data QueryStage
= FetchColumns | WithMergeableState | Complete
| WithMergeableStateAfterAggregation
| WithMergeableStateAfterAggregationAndLimit
deriving (Int -> QueryStage
QueryStage -> Int
QueryStage -> [QueryStage]
QueryStage -> QueryStage
QueryStage -> QueryStage -> [QueryStage]
QueryStage -> QueryStage -> QueryStage -> [QueryStage]
(QueryStage -> QueryStage)
-> (QueryStage -> QueryStage)
-> (Int -> QueryStage)
-> (QueryStage -> Int)
-> (QueryStage -> [QueryStage])
-> (QueryStage -> QueryStage -> [QueryStage])
-> (QueryStage -> QueryStage -> [QueryStage])
-> (QueryStage -> QueryStage -> QueryStage -> [QueryStage])
-> Enum QueryStage
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: QueryStage -> QueryStage
succ :: QueryStage -> QueryStage
$cpred :: QueryStage -> QueryStage
pred :: QueryStage -> QueryStage
$ctoEnum :: Int -> QueryStage
toEnum :: Int -> QueryStage
$cfromEnum :: QueryStage -> Int
fromEnum :: QueryStage -> Int
$cenumFrom :: QueryStage -> [QueryStage]
enumFrom :: QueryStage -> [QueryStage]
$cenumFromThen :: QueryStage -> QueryStage -> [QueryStage]
enumFromThen :: QueryStage -> QueryStage -> [QueryStage]
$cenumFromTo :: QueryStage -> QueryStage -> [QueryStage]
enumFromTo :: QueryStage -> QueryStage -> [QueryStage]
$cenumFromThenTo :: QueryStage -> QueryStage -> QueryStage -> [QueryStage]
enumFromThenTo :: QueryStage -> QueryStage -> QueryStage -> [QueryStage]
Enum)
instance Serializable QueryStage where
serialize :: ProtocolRevision -> QueryStage -> Builder
serialize ProtocolRevision
rev = forall chType.
Serializable chType =>
ProtocolRevision -> chType -> Builder
serialize @UVarInt ProtocolRevision
rev (UVarInt -> Builder)
-> (QueryStage -> UVarInt) -> QueryStage -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> UVarInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> UVarInt) -> (QueryStage -> Int) -> QueryStage -> UVarInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QueryStage -> Int
forall a. Enum a => a -> Int
fromEnum
data Flags = IMPORTANT | CUSTOM | OBSOLETE
_flagCode :: Flags -> UInt64
_flagCode :: Flags -> UInt64
_flagCode Flags
IMPORTANT = UInt64
0x01
_flagCode Flags
CUSTOM = UInt64
0x02
_flagCode Flags
OBSOLETE = UInt64
0x04
data ClientInfo = MkClientInfo
{ ClientInfo -> QueryKind
query_kind :: QueryKind
, ClientInfo -> ChString
initial_user :: ChString
, ClientInfo -> ChString
initial_query_id :: ChString
, ClientInfo -> ChString
initial_adress :: ChString
, ClientInfo
-> SinceRevision
Int64 DBMS_MIN_PROTOCOL_VERSION_WITH_INITIAL_QUERY_START_TIME
initial_time :: Int64 `SinceRevision` DBMS_MIN_PROTOCOL_VERSION_WITH_INITIAL_QUERY_START_TIME
, ClientInfo -> UInt8
interface_type :: UInt8
, ClientInfo -> ChString
os_user :: ChString
, ClientInfo -> ChString
hostname :: ChString
, ClientInfo -> ChString
client_name :: ChString
, ClientInfo -> UVarInt
client_version_major :: UVarInt
, ClientInfo -> UVarInt
client_version_minor :: UVarInt
, ClientInfo -> ProtocolRevision
client_revision :: ProtocolRevision
, ClientInfo
-> SinceRevision
ChString DBMS_MIN_REVISION_WITH_QUOTA_KEY_IN_CLIENT_INFO
quota_key :: ChString `SinceRevision` DBMS_MIN_REVISION_WITH_QUOTA_KEY_IN_CLIENT_INFO
, ClientInfo
-> SinceRevision
UVarInt DBMS_MIN_PROTOCOL_VERSION_WITH_DISTRIBUTED_DEPTH
distrubuted_depth :: UVarInt `SinceRevision` DBMS_MIN_PROTOCOL_VERSION_WITH_DISTRIBUTED_DEPTH
, ClientInfo
-> SinceRevision UVarInt DBMS_MIN_REVISION_WITH_VERSION_PATCH
client_version_patch :: UVarInt `SinceRevision` DBMS_MIN_REVISION_WITH_VERSION_PATCH
, ClientInfo
-> SinceRevision UInt8 DBMS_MIN_REVISION_WITH_OPENTELEMETRY
open_telemetry :: UInt8 `SinceRevision` DBMS_MIN_REVISION_WITH_OPENTELEMETRY
, ClientInfo
-> SinceRevision UVarInt DBMS_MIN_REVISION_WITH_PARALLEL_REPLICAS
collaborate_with_initiator :: UVarInt `SinceRevision` DBMS_MIN_REVISION_WITH_PARALLEL_REPLICAS
, ClientInfo
-> SinceRevision UVarInt DBMS_MIN_REVISION_WITH_PARALLEL_REPLICAS
count_participating_replicas :: UVarInt `SinceRevision` DBMS_MIN_REVISION_WITH_PARALLEL_REPLICAS
, ClientInfo
-> SinceRevision UVarInt DBMS_MIN_REVISION_WITH_PARALLEL_REPLICAS
number_of_current_replica :: UVarInt `SinceRevision` DBMS_MIN_REVISION_WITH_PARALLEL_REPLICAS
}
deriving ((forall x. ClientInfo -> Rep ClientInfo x)
-> (forall x. Rep ClientInfo x -> ClientInfo) -> Generic ClientInfo
forall x. Rep ClientInfo x -> ClientInfo
forall x. ClientInfo -> Rep ClientInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ClientInfo -> Rep ClientInfo x
from :: forall x. ClientInfo -> Rep ClientInfo x
$cto :: forall x. Rep ClientInfo x -> ClientInfo
to :: forall x. Rep ClientInfo x -> ClientInfo
Generic, ProtocolRevision -> ClientInfo -> Builder
(ProtocolRevision -> ClientInfo -> Builder)
-> Serializable ClientInfo
forall chType.
(ProtocolRevision -> chType -> Builder) -> Serializable chType
$cserialize :: ProtocolRevision -> ClientInfo -> Builder
serialize :: ProtocolRevision -> ClientInfo -> Builder
Serializable)
data QueryKind = NoQuery | InitialQuery | SecondaryQuery
instance Serializable QueryKind where
serialize :: ProtocolRevision -> QueryKind -> Builder
serialize ProtocolRevision
rev = forall chType.
Serializable chType =>
ProtocolRevision -> chType -> Builder
serialize @UInt8 ProtocolRevision
rev (UInt8 -> Builder) -> (QueryKind -> UInt8) -> QueryKind -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\case QueryKind
NoQuery -> UInt8
1; QueryKind
InitialQuery -> UInt8
2; QueryKind
SecondaryQuery -> UInt8
3)