module ClickHaskell.Primitive where

-- Internal
import Paths_ClickHaskell (version)

-- GHC included
import Control.Applicative (liftA2)
import Control.DeepSeq (NFData)
import Control.Monad ((<=<))
import Data.Binary.Get
import Data.Bits (Bits (setBit, unsafeShiftL, unsafeShiftR, (.&.), (.|.)))
import Data.ByteString as BS (ByteString, length)
import Data.ByteString.Builder
import Data.Coerce (coerce)
import Data.Int (Int16, Int32, Int64, Int8)
import Data.String (IsString (..))
import Data.Typeable (Proxy (..))
import Data.Version (Version (..))
import Data.Word (Word16, Word32, Word64, Word8)
import GHC.Generics (C1, D1, Generic (..), K1 (K1), M1 (M1), Rec0, S1, type (:*:) (..))
import GHC.TypeLits (ErrorMessage (..), KnownNat, KnownSymbol, Nat, Symbol, TypeError, natVal, symbolVal)
import Prelude hiding (liftA2)

-- External
import Data.WideWord (Int128 (..), Word128(..))

-- * 

class IsChType chType
  where
  -- | Shows database original type name
  --
  -- @
  -- chTypeName \@ChString = \"String\"
  -- chTypeName \@(Nullable UInt32) = \"Nullable(UInt32)\"
  -- @
  chTypeName :: String

  defaultValueOfTypeName :: chType

instance IsChType Int8 where; chTypeName :: String
chTypeName = String
"Int8"; defaultValueOfTypeName :: Int8
defaultValueOfTypeName = Int8
0
instance IsChType Int16 where; chTypeName :: String
chTypeName = String
"Int16"; defaultValueOfTypeName :: Int16
defaultValueOfTypeName = Int16
0
instance IsChType Int32 where; chTypeName :: String
chTypeName = String
"Int32"; defaultValueOfTypeName :: Int32
defaultValueOfTypeName = Int32
0
instance IsChType Int64 where; chTypeName :: String
chTypeName = String
"Int64"; defaultValueOfTypeName :: Int64
defaultValueOfTypeName = Int64
0
instance IsChType Int128 where; chTypeName :: String
chTypeName = String
"Int128"; defaultValueOfTypeName :: Int128
defaultValueOfTypeName = Int128
0

{- | ClickHouse UInt8 column type -}
type UInt8 = Word8
instance IsChType UInt8 where; chTypeName :: String
chTypeName = String
"UInt8"; defaultValueOfTypeName :: UInt8
defaultValueOfTypeName = UInt8
0

{- | ClickHouse UInt16 column type -}
type UInt16 = Word16
instance IsChType UInt16 where; chTypeName :: String
chTypeName = String
"UInt16"; defaultValueOfTypeName :: UInt16
defaultValueOfTypeName = UInt16
0

{- | ClickHouse UInt32 column type -}
type UInt32 = Word32
instance IsChType UInt32 where; chTypeName :: String
chTypeName = String
"UInt32"; defaultValueOfTypeName :: UInt32
defaultValueOfTypeName = UInt32
0

{- | ClickHouse UInt64 column type -}
type UInt64 = Word64
instance IsChType UInt64 where; chTypeName :: String
chTypeName = String
"UInt64"; defaultValueOfTypeName :: UInt64
defaultValueOfTypeName = UInt64
0

{- | ClickHouse UInt128 column type -}
type UInt128 = Word128
instance IsChType UInt128 where; chTypeName :: String
chTypeName = String
"UInt128"; defaultValueOfTypeName :: UInt128
defaultValueOfTypeName = UInt128
0

{- | ClickHouse Date column type -}
newtype Date = MkDate Word16
  deriving newtype (Int -> Date -> ShowS
[Date] -> ShowS
Date -> String
(Int -> Date -> ShowS)
-> (Date -> String) -> ([Date] -> ShowS) -> Show Date
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Date -> ShowS
showsPrec :: Int -> Date -> ShowS
$cshow :: Date -> String
show :: Date -> String
$cshowList :: [Date] -> ShowS
showList :: [Date] -> ShowS
Show, Date -> Date -> Bool
(Date -> Date -> Bool) -> (Date -> Date -> Bool) -> Eq Date
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Date -> Date -> Bool
== :: Date -> Date -> Bool
$c/= :: Date -> Date -> Bool
/= :: Date -> Date -> Bool
Eq, Eq Date
Date
Eq Date =>
(Date -> Date -> Date)
-> (Date -> Date -> Date)
-> (Date -> Date -> Date)
-> (Date -> Date)
-> (Date -> Int -> Date)
-> (Date -> Int -> Date)
-> Date
-> (Int -> Date)
-> (Date -> Int -> Date)
-> (Date -> Int -> Date)
-> (Date -> Int -> Date)
-> (Date -> Int -> Bool)
-> (Date -> Maybe Int)
-> (Date -> Int)
-> (Date -> Bool)
-> (Date -> Int -> Date)
-> (Date -> Int -> Date)
-> (Date -> Int -> Date)
-> (Date -> Int -> Date)
-> (Date -> Int -> Date)
-> (Date -> Int -> Date)
-> (Date -> Int)
-> Bits Date
Int -> Date
Date -> Bool
Date -> Int
Date -> Maybe Int
Date -> Date
Date -> Int -> Bool
Date -> Int -> Date
Date -> Date -> Date
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
$c.&. :: Date -> Date -> Date
.&. :: Date -> Date -> Date
$c.|. :: Date -> Date -> Date
.|. :: Date -> Date -> Date
$cxor :: Date -> Date -> Date
xor :: Date -> Date -> Date
$ccomplement :: Date -> Date
complement :: Date -> Date
$cshift :: Date -> Int -> Date
shift :: Date -> Int -> Date
$crotate :: Date -> Int -> Date
rotate :: Date -> Int -> Date
$czeroBits :: Date
zeroBits :: Date
$cbit :: Int -> Date
bit :: Int -> Date
$csetBit :: Date -> Int -> Date
setBit :: Date -> Int -> Date
$cclearBit :: Date -> Int -> Date
clearBit :: Date -> Int -> Date
$ccomplementBit :: Date -> Int -> Date
complementBit :: Date -> Int -> Date
$ctestBit :: Date -> Int -> Bool
testBit :: Date -> Int -> Bool
$cbitSizeMaybe :: Date -> Maybe Int
bitSizeMaybe :: Date -> Maybe Int
$cbitSize :: Date -> Int
bitSize :: Date -> Int
$cisSigned :: Date -> Bool
isSigned :: Date -> Bool
$cshiftL :: Date -> Int -> Date
shiftL :: Date -> Int -> Date
$cunsafeShiftL :: Date -> Int -> Date
unsafeShiftL :: Date -> Int -> Date
$cshiftR :: Date -> Int -> Date
shiftR :: Date -> Int -> Date
$cunsafeShiftR :: Date -> Int -> Date
unsafeShiftR :: Date -> Int -> Date
$crotateL :: Date -> Int -> Date
rotateL :: Date -> Int -> Date
$crotateR :: Date -> Int -> Date
rotateR :: Date -> Int -> Date
$cpopCount :: Date -> Int
popCount :: Date -> Int
Bits, Date
Date -> Date -> Bounded Date
forall a. a -> a -> Bounded a
$cminBound :: Date
minBound :: Date
$cmaxBound :: Date
maxBound :: Date
Bounded, Int -> Date
Date -> Int
Date -> [Date]
Date -> Date
Date -> Date -> [Date]
Date -> Date -> Date -> [Date]
(Date -> Date)
-> (Date -> Date)
-> (Int -> Date)
-> (Date -> Int)
-> (Date -> [Date])
-> (Date -> Date -> [Date])
-> (Date -> Date -> [Date])
-> (Date -> Date -> Date -> [Date])
-> Enum Date
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 :: Date -> Date
succ :: Date -> Date
$cpred :: Date -> Date
pred :: Date -> Date
$ctoEnum :: Int -> Date
toEnum :: Int -> Date
$cfromEnum :: Date -> Int
fromEnum :: Date -> Int
$cenumFrom :: Date -> [Date]
enumFrom :: Date -> [Date]
$cenumFromThen :: Date -> Date -> [Date]
enumFromThen :: Date -> Date -> [Date]
$cenumFromTo :: Date -> Date -> [Date]
enumFromTo :: Date -> Date -> [Date]
$cenumFromThenTo :: Date -> Date -> Date -> [Date]
enumFromThenTo :: Date -> Date -> Date -> [Date]
Enum, Date -> ()
(Date -> ()) -> NFData Date
forall a. (a -> ()) -> NFData a
$crnf :: Date -> ()
rnf :: Date -> ()
NFData, Integer -> Date
Date -> Date
Date -> Date -> Date
(Date -> Date -> Date)
-> (Date -> Date -> Date)
-> (Date -> Date -> Date)
-> (Date -> Date)
-> (Date -> Date)
-> (Date -> Date)
-> (Integer -> Date)
-> Num Date
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: Date -> Date -> Date
+ :: Date -> Date -> Date
$c- :: Date -> Date -> Date
- :: Date -> Date -> Date
$c* :: Date -> Date -> Date
* :: Date -> Date -> Date
$cnegate :: Date -> Date
negate :: Date -> Date
$cabs :: Date -> Date
abs :: Date -> Date
$csignum :: Date -> Date
signum :: Date -> Date
$cfromInteger :: Integer -> Date
fromInteger :: Integer -> Date
Num)
instance IsChType Date where; chTypeName :: String
chTypeName = String
"Date"; defaultValueOfTypeName :: Date
defaultValueOfTypeName = Date
0

{- | ClickHouse String column type -}
newtype ChString = MkChString BS.ByteString
  deriving newtype (Int -> ChString -> ShowS
[ChString] -> ShowS
ChString -> String
(Int -> ChString -> ShowS)
-> (ChString -> String) -> ([ChString] -> ShowS) -> Show ChString
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ChString -> ShowS
showsPrec :: Int -> ChString -> ShowS
$cshow :: ChString -> String
show :: ChString -> String
$cshowList :: [ChString] -> ShowS
showList :: [ChString] -> ShowS
Show, ChString -> ChString -> Bool
(ChString -> ChString -> Bool)
-> (ChString -> ChString -> Bool) -> Eq ChString
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ChString -> ChString -> Bool
== :: ChString -> ChString -> Bool
$c/= :: ChString -> ChString -> Bool
/= :: ChString -> ChString -> Bool
Eq, String -> ChString
(String -> ChString) -> IsString ChString
forall a. (String -> a) -> IsString a
$cfromString :: String -> ChString
fromString :: String -> ChString
IsString, ChString -> ()
(ChString -> ()) -> NFData ChString
forall a. (a -> ()) -> NFData a
$crnf :: ChString -> ()
rnf :: ChString -> ()
NFData)
instance IsChType ChString where; chTypeName :: String
chTypeName = String
"String"; defaultValueOfTypeName :: ChString
defaultValueOfTypeName = ChString
""

{- | ClickHouse UUID column type -}
newtype UUID = MkUUID Word128
  deriving newtype ((forall x. UUID -> Rep UUID x)
-> (forall x. Rep UUID x -> UUID) -> Generic UUID
forall x. Rep UUID x -> UUID
forall x. UUID -> Rep UUID x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. UUID -> Rep UUID x
from :: forall x. UUID -> Rep UUID x
$cto :: forall x. Rep UUID x -> UUID
to :: forall x. Rep UUID x -> UUID
Generic, Int -> UUID -> ShowS
[UUID] -> ShowS
UUID -> String
(Int -> UUID -> ShowS)
-> (UUID -> String) -> ([UUID] -> ShowS) -> Show UUID
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UUID -> ShowS
showsPrec :: Int -> UUID -> ShowS
$cshow :: UUID -> String
show :: UUID -> String
$cshowList :: [UUID] -> ShowS
showList :: [UUID] -> ShowS
Show, UUID -> UUID -> Bool
(UUID -> UUID -> Bool) -> (UUID -> UUID -> Bool) -> Eq UUID
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UUID -> UUID -> Bool
== :: UUID -> UUID -> Bool
$c/= :: UUID -> UUID -> Bool
/= :: UUID -> UUID -> Bool
Eq, UUID -> ()
(UUID -> ()) -> NFData UUID
forall a. (a -> ()) -> NFData a
$crnf :: UUID -> ()
rnf :: UUID -> ()
NFData, UUID
UUID -> UUID -> Bounded UUID
forall a. a -> a -> Bounded a
$cminBound :: UUID
minBound :: UUID
$cmaxBound :: UUID
maxBound :: UUID
Bounded, Int -> UUID
UUID -> Int
UUID -> [UUID]
UUID -> UUID
UUID -> UUID -> [UUID]
UUID -> UUID -> UUID -> [UUID]
(UUID -> UUID)
-> (UUID -> UUID)
-> (Int -> UUID)
-> (UUID -> Int)
-> (UUID -> [UUID])
-> (UUID -> UUID -> [UUID])
-> (UUID -> UUID -> [UUID])
-> (UUID -> UUID -> UUID -> [UUID])
-> Enum UUID
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 :: UUID -> UUID
succ :: UUID -> UUID
$cpred :: UUID -> UUID
pred :: UUID -> UUID
$ctoEnum :: Int -> UUID
toEnum :: Int -> UUID
$cfromEnum :: UUID -> Int
fromEnum :: UUID -> Int
$cenumFrom :: UUID -> [UUID]
enumFrom :: UUID -> [UUID]
$cenumFromThen :: UUID -> UUID -> [UUID]
enumFromThen :: UUID -> UUID -> [UUID]
$cenumFromTo :: UUID -> UUID -> [UUID]
enumFromTo :: UUID -> UUID -> [UUID]
$cenumFromThenTo :: UUID -> UUID -> UUID -> [UUID]
enumFromThenTo :: UUID -> UUID -> UUID -> [UUID]
Enum, Integer -> UUID
UUID -> UUID
UUID -> UUID -> UUID
(UUID -> UUID -> UUID)
-> (UUID -> UUID -> UUID)
-> (UUID -> UUID -> UUID)
-> (UUID -> UUID)
-> (UUID -> UUID)
-> (UUID -> UUID)
-> (Integer -> UUID)
-> Num UUID
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: UUID -> UUID -> UUID
+ :: UUID -> UUID -> UUID
$c- :: UUID -> UUID -> UUID
- :: UUID -> UUID -> UUID
$c* :: UUID -> UUID -> UUID
* :: UUID -> UUID -> UUID
$cnegate :: UUID -> UUID
negate :: UUID -> UUID
$cabs :: UUID -> UUID
abs :: UUID -> UUID
$csignum :: UUID -> UUID
signum :: UUID -> UUID
$cfromInteger :: Integer -> UUID
fromInteger :: Integer -> UUID
Num)
instance IsChType UUID where; chTypeName :: String
chTypeName = String
"UUID"; defaultValueOfTypeName :: UUID
defaultValueOfTypeName = UUID
0

{- | ClickHouse Nullable(T) column type
 (type synonym for Maybe)
 -}
type Nullable = Maybe
instance IsChType chType => IsChType (Nullable chType)
  where
  chTypeName :: String
chTypeName = String
"Nullable(" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> forall chType. IsChType chType => String
chTypeName @chType String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
")"
  defaultValueOfTypeName :: Nullable chType
defaultValueOfTypeName = Nullable chType
forall a. Maybe a
Nothing

{- |
ClickHouse DateTime column type (paramtrized with timezone)

>>> chTypeName @(DateTime "")
"DateTime"
>>> chTypeName @(DateTime "UTC")
"DateTime('UTC')"
-}
newtype DateTime (tz :: Symbol) = MkDateTime Word32
  deriving newtype (Int -> DateTime tz -> ShowS
[DateTime tz] -> ShowS
DateTime tz -> String
(Int -> DateTime tz -> ShowS)
-> (DateTime tz -> String)
-> ([DateTime tz] -> ShowS)
-> Show (DateTime tz)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (tz :: Symbol). Int -> DateTime tz -> ShowS
forall (tz :: Symbol). [DateTime tz] -> ShowS
forall (tz :: Symbol). DateTime tz -> String
$cshowsPrec :: forall (tz :: Symbol). Int -> DateTime tz -> ShowS
showsPrec :: Int -> DateTime tz -> ShowS
$cshow :: forall (tz :: Symbol). DateTime tz -> String
show :: DateTime tz -> String
$cshowList :: forall (tz :: Symbol). [DateTime tz] -> ShowS
showList :: [DateTime tz] -> ShowS
Show, DateTime tz -> DateTime tz -> Bool
(DateTime tz -> DateTime tz -> Bool)
-> (DateTime tz -> DateTime tz -> Bool) -> Eq (DateTime tz)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (tz :: Symbol). DateTime tz -> DateTime tz -> Bool
$c== :: forall (tz :: Symbol). DateTime tz -> DateTime tz -> Bool
== :: DateTime tz -> DateTime tz -> Bool
$c/= :: forall (tz :: Symbol). DateTime tz -> DateTime tz -> Bool
/= :: DateTime tz -> DateTime tz -> Bool
Eq, Integer -> DateTime tz
DateTime tz -> DateTime tz
DateTime tz -> DateTime tz -> DateTime tz
(DateTime tz -> DateTime tz -> DateTime tz)
-> (DateTime tz -> DateTime tz -> DateTime tz)
-> (DateTime tz -> DateTime tz -> DateTime tz)
-> (DateTime tz -> DateTime tz)
-> (DateTime tz -> DateTime tz)
-> (DateTime tz -> DateTime tz)
-> (Integer -> DateTime tz)
-> Num (DateTime tz)
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
forall (tz :: Symbol). Integer -> DateTime tz
forall (tz :: Symbol). DateTime tz -> DateTime tz
forall (tz :: Symbol). DateTime tz -> DateTime tz -> DateTime tz
$c+ :: forall (tz :: Symbol). DateTime tz -> DateTime tz -> DateTime tz
+ :: DateTime tz -> DateTime tz -> DateTime tz
$c- :: forall (tz :: Symbol). DateTime tz -> DateTime tz -> DateTime tz
- :: DateTime tz -> DateTime tz -> DateTime tz
$c* :: forall (tz :: Symbol). DateTime tz -> DateTime tz -> DateTime tz
* :: DateTime tz -> DateTime tz -> DateTime tz
$cnegate :: forall (tz :: Symbol). DateTime tz -> DateTime tz
negate :: DateTime tz -> DateTime tz
$cabs :: forall (tz :: Symbol). DateTime tz -> DateTime tz
abs :: DateTime tz -> DateTime tz
$csignum :: forall (tz :: Symbol). DateTime tz -> DateTime tz
signum :: DateTime tz -> DateTime tz
$cfromInteger :: forall (tz :: Symbol). Integer -> DateTime tz
fromInteger :: Integer -> DateTime tz
Num, Eq (DateTime tz)
DateTime tz
Eq (DateTime tz) =>
(DateTime tz -> DateTime tz -> DateTime tz)
-> (DateTime tz -> DateTime tz -> DateTime tz)
-> (DateTime tz -> DateTime tz -> DateTime tz)
-> (DateTime tz -> DateTime tz)
-> (DateTime tz -> Int -> DateTime tz)
-> (DateTime tz -> Int -> DateTime tz)
-> DateTime tz
-> (Int -> DateTime tz)
-> (DateTime tz -> Int -> DateTime tz)
-> (DateTime tz -> Int -> DateTime tz)
-> (DateTime tz -> Int -> DateTime tz)
-> (DateTime tz -> Int -> Bool)
-> (DateTime tz -> Maybe Int)
-> (DateTime tz -> Int)
-> (DateTime tz -> Bool)
-> (DateTime tz -> Int -> DateTime tz)
-> (DateTime tz -> Int -> DateTime tz)
-> (DateTime tz -> Int -> DateTime tz)
-> (DateTime tz -> Int -> DateTime tz)
-> (DateTime tz -> Int -> DateTime tz)
-> (DateTime tz -> Int -> DateTime tz)
-> (DateTime tz -> Int)
-> Bits (DateTime tz)
Int -> DateTime tz
DateTime tz -> Bool
DateTime tz -> Int
DateTime tz -> Maybe Int
DateTime tz -> DateTime tz
DateTime tz -> Int -> Bool
DateTime tz -> Int -> DateTime tz
DateTime tz -> DateTime tz -> DateTime tz
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
forall (tz :: Symbol). Eq (DateTime tz)
forall (tz :: Symbol). DateTime tz
forall (tz :: Symbol). Int -> DateTime tz
forall (tz :: Symbol). DateTime tz -> Bool
forall (tz :: Symbol). DateTime tz -> Int
forall (tz :: Symbol). DateTime tz -> Maybe Int
forall (tz :: Symbol). DateTime tz -> DateTime tz
forall (tz :: Symbol). DateTime tz -> Int -> Bool
forall (tz :: Symbol). DateTime tz -> Int -> DateTime tz
forall (tz :: Symbol). DateTime tz -> DateTime tz -> DateTime tz
$c.&. :: forall (tz :: Symbol). DateTime tz -> DateTime tz -> DateTime tz
.&. :: DateTime tz -> DateTime tz -> DateTime tz
$c.|. :: forall (tz :: Symbol). DateTime tz -> DateTime tz -> DateTime tz
.|. :: DateTime tz -> DateTime tz -> DateTime tz
$cxor :: forall (tz :: Symbol). DateTime tz -> DateTime tz -> DateTime tz
xor :: DateTime tz -> DateTime tz -> DateTime tz
$ccomplement :: forall (tz :: Symbol). DateTime tz -> DateTime tz
complement :: DateTime tz -> DateTime tz
$cshift :: forall (tz :: Symbol). DateTime tz -> Int -> DateTime tz
shift :: DateTime tz -> Int -> DateTime tz
$crotate :: forall (tz :: Symbol). DateTime tz -> Int -> DateTime tz
rotate :: DateTime tz -> Int -> DateTime tz
$czeroBits :: forall (tz :: Symbol). DateTime tz
zeroBits :: DateTime tz
$cbit :: forall (tz :: Symbol). Int -> DateTime tz
bit :: Int -> DateTime tz
$csetBit :: forall (tz :: Symbol). DateTime tz -> Int -> DateTime tz
setBit :: DateTime tz -> Int -> DateTime tz
$cclearBit :: forall (tz :: Symbol). DateTime tz -> Int -> DateTime tz
clearBit :: DateTime tz -> Int -> DateTime tz
$ccomplementBit :: forall (tz :: Symbol). DateTime tz -> Int -> DateTime tz
complementBit :: DateTime tz -> Int -> DateTime tz
$ctestBit :: forall (tz :: Symbol). DateTime tz -> Int -> Bool
testBit :: DateTime tz -> Int -> Bool
$cbitSizeMaybe :: forall (tz :: Symbol). DateTime tz -> Maybe Int
bitSizeMaybe :: DateTime tz -> Maybe Int
$cbitSize :: forall (tz :: Symbol). DateTime tz -> Int
bitSize :: DateTime tz -> Int
$cisSigned :: forall (tz :: Symbol). DateTime tz -> Bool
isSigned :: DateTime tz -> Bool
$cshiftL :: forall (tz :: Symbol). DateTime tz -> Int -> DateTime tz
shiftL :: DateTime tz -> Int -> DateTime tz
$cunsafeShiftL :: forall (tz :: Symbol). DateTime tz -> Int -> DateTime tz
unsafeShiftL :: DateTime tz -> Int -> DateTime tz
$cshiftR :: forall (tz :: Symbol). DateTime tz -> Int -> DateTime tz
shiftR :: DateTime tz -> Int -> DateTime tz
$cunsafeShiftR :: forall (tz :: Symbol). DateTime tz -> Int -> DateTime tz
unsafeShiftR :: DateTime tz -> Int -> DateTime tz
$crotateL :: forall (tz :: Symbol). DateTime tz -> Int -> DateTime tz
rotateL :: DateTime tz -> Int -> DateTime tz
$crotateR :: forall (tz :: Symbol). DateTime tz -> Int -> DateTime tz
rotateR :: DateTime tz -> Int -> DateTime tz
$cpopCount :: forall (tz :: Symbol). DateTime tz -> Int
popCount :: DateTime tz -> Int
Bits, Int -> DateTime tz
DateTime tz -> Int
DateTime tz -> [DateTime tz]
DateTime tz -> DateTime tz
DateTime tz -> DateTime tz -> [DateTime tz]
DateTime tz -> DateTime tz -> DateTime tz -> [DateTime tz]
(DateTime tz -> DateTime tz)
-> (DateTime tz -> DateTime tz)
-> (Int -> DateTime tz)
-> (DateTime tz -> Int)
-> (DateTime tz -> [DateTime tz])
-> (DateTime tz -> DateTime tz -> [DateTime tz])
-> (DateTime tz -> DateTime tz -> [DateTime tz])
-> (DateTime tz -> DateTime tz -> DateTime tz -> [DateTime tz])
-> Enum (DateTime tz)
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
forall (tz :: Symbol). Int -> DateTime tz
forall (tz :: Symbol). DateTime tz -> Int
forall (tz :: Symbol). DateTime tz -> [DateTime tz]
forall (tz :: Symbol). DateTime tz -> DateTime tz
forall (tz :: Symbol). DateTime tz -> DateTime tz -> [DateTime tz]
forall (tz :: Symbol).
DateTime tz -> DateTime tz -> DateTime tz -> [DateTime tz]
$csucc :: forall (tz :: Symbol). DateTime tz -> DateTime tz
succ :: DateTime tz -> DateTime tz
$cpred :: forall (tz :: Symbol). DateTime tz -> DateTime tz
pred :: DateTime tz -> DateTime tz
$ctoEnum :: forall (tz :: Symbol). Int -> DateTime tz
toEnum :: Int -> DateTime tz
$cfromEnum :: forall (tz :: Symbol). DateTime tz -> Int
fromEnum :: DateTime tz -> Int
$cenumFrom :: forall (tz :: Symbol). DateTime tz -> [DateTime tz]
enumFrom :: DateTime tz -> [DateTime tz]
$cenumFromThen :: forall (tz :: Symbol). DateTime tz -> DateTime tz -> [DateTime tz]
enumFromThen :: DateTime tz -> DateTime tz -> [DateTime tz]
$cenumFromTo :: forall (tz :: Symbol). DateTime tz -> DateTime tz -> [DateTime tz]
enumFromTo :: DateTime tz -> DateTime tz -> [DateTime tz]
$cenumFromThenTo :: forall (tz :: Symbol).
DateTime tz -> DateTime tz -> DateTime tz -> [DateTime tz]
enumFromThenTo :: DateTime tz -> DateTime tz -> DateTime tz -> [DateTime tz]
Enum, Eq (DateTime tz)
Eq (DateTime tz) =>
(DateTime tz -> DateTime tz -> Ordering)
-> (DateTime tz -> DateTime tz -> Bool)
-> (DateTime tz -> DateTime tz -> Bool)
-> (DateTime tz -> DateTime tz -> Bool)
-> (DateTime tz -> DateTime tz -> Bool)
-> (DateTime tz -> DateTime tz -> DateTime tz)
-> (DateTime tz -> DateTime tz -> DateTime tz)
-> Ord (DateTime tz)
DateTime tz -> DateTime tz -> Bool
DateTime tz -> DateTime tz -> Ordering
DateTime tz -> DateTime tz -> DateTime tz
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall (tz :: Symbol). Eq (DateTime tz)
forall (tz :: Symbol). DateTime tz -> DateTime tz -> Bool
forall (tz :: Symbol). DateTime tz -> DateTime tz -> Ordering
forall (tz :: Symbol). DateTime tz -> DateTime tz -> DateTime tz
$ccompare :: forall (tz :: Symbol). DateTime tz -> DateTime tz -> Ordering
compare :: DateTime tz -> DateTime tz -> Ordering
$c< :: forall (tz :: Symbol). DateTime tz -> DateTime tz -> Bool
< :: DateTime tz -> DateTime tz -> Bool
$c<= :: forall (tz :: Symbol). DateTime tz -> DateTime tz -> Bool
<= :: DateTime tz -> DateTime tz -> Bool
$c> :: forall (tz :: Symbol). DateTime tz -> DateTime tz -> Bool
> :: DateTime tz -> DateTime tz -> Bool
$c>= :: forall (tz :: Symbol). DateTime tz -> DateTime tz -> Bool
>= :: DateTime tz -> DateTime tz -> Bool
$cmax :: forall (tz :: Symbol). DateTime tz -> DateTime tz -> DateTime tz
max :: DateTime tz -> DateTime tz -> DateTime tz
$cmin :: forall (tz :: Symbol). DateTime tz -> DateTime tz -> DateTime tz
min :: DateTime tz -> DateTime tz -> DateTime tz
Ord, Num (DateTime tz)
Ord (DateTime tz)
(Num (DateTime tz), Ord (DateTime tz)) =>
(DateTime tz -> Rational) -> Real (DateTime tz)
DateTime tz -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
forall (tz :: Symbol). Num (DateTime tz)
forall (tz :: Symbol). Ord (DateTime tz)
forall (tz :: Symbol). DateTime tz -> Rational
$ctoRational :: forall (tz :: Symbol). DateTime tz -> Rational
toRational :: DateTime tz -> Rational
Real, Enum (DateTime tz)
Real (DateTime tz)
(Real (DateTime tz), Enum (DateTime tz)) =>
(DateTime tz -> DateTime tz -> DateTime tz)
-> (DateTime tz -> DateTime tz -> DateTime tz)
-> (DateTime tz -> DateTime tz -> DateTime tz)
-> (DateTime tz -> DateTime tz -> DateTime tz)
-> (DateTime tz -> DateTime tz -> (DateTime tz, DateTime tz))
-> (DateTime tz -> DateTime tz -> (DateTime tz, DateTime tz))
-> (DateTime tz -> Integer)
-> Integral (DateTime tz)
DateTime tz -> Integer
DateTime tz -> DateTime tz -> (DateTime tz, DateTime tz)
DateTime tz -> DateTime tz -> DateTime tz
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
forall (tz :: Symbol). Enum (DateTime tz)
forall (tz :: Symbol). Real (DateTime tz)
forall (tz :: Symbol). DateTime tz -> Integer
forall (tz :: Symbol).
DateTime tz -> DateTime tz -> (DateTime tz, DateTime tz)
forall (tz :: Symbol). DateTime tz -> DateTime tz -> DateTime tz
$cquot :: forall (tz :: Symbol). DateTime tz -> DateTime tz -> DateTime tz
quot :: DateTime tz -> DateTime tz -> DateTime tz
$crem :: forall (tz :: Symbol). DateTime tz -> DateTime tz -> DateTime tz
rem :: DateTime tz -> DateTime tz -> DateTime tz
$cdiv :: forall (tz :: Symbol). DateTime tz -> DateTime tz -> DateTime tz
div :: DateTime tz -> DateTime tz -> DateTime tz
$cmod :: forall (tz :: Symbol). DateTime tz -> DateTime tz -> DateTime tz
mod :: DateTime tz -> DateTime tz -> DateTime tz
$cquotRem :: forall (tz :: Symbol).
DateTime tz -> DateTime tz -> (DateTime tz, DateTime tz)
quotRem :: DateTime tz -> DateTime tz -> (DateTime tz, DateTime tz)
$cdivMod :: forall (tz :: Symbol).
DateTime tz -> DateTime tz -> (DateTime tz, DateTime tz)
divMod :: DateTime tz -> DateTime tz -> (DateTime tz, DateTime tz)
$ctoInteger :: forall (tz :: Symbol). DateTime tz -> Integer
toInteger :: DateTime tz -> Integer
Integral, DateTime tz
DateTime tz -> DateTime tz -> Bounded (DateTime tz)
forall a. a -> a -> Bounded a
forall (tz :: Symbol). DateTime tz
$cminBound :: forall (tz :: Symbol). DateTime tz
minBound :: DateTime tz
$cmaxBound :: forall (tz :: Symbol). DateTime tz
maxBound :: DateTime tz
Bounded, DateTime tz -> ()
(DateTime tz -> ()) -> NFData (DateTime tz)
forall a. (a -> ()) -> NFData a
forall (tz :: Symbol). DateTime tz -> ()
$crnf :: forall (tz :: Symbol). DateTime tz -> ()
rnf :: DateTime tz -> ()
NFData)

instance KnownSymbol tz => IsChType (DateTime tz)
  where
  chTypeName :: String
chTypeName = case (forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal @tz Proxy tz
forall {k} (t :: k). Proxy t
Proxy) of
    String
"" -> String
"DateTime"
    String
tz -> String
"DateTime('" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
tz String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"')" 
  defaultValueOfTypeName :: DateTime tz
defaultValueOfTypeName = UInt32 -> DateTime tz
forall (tz :: Symbol). UInt32 -> DateTime tz
MkDateTime UInt32
0

{- |
ClickHouse DateTime64 column type (paramtrized with timezone)

>>> chTypeName @(DateTime64 3 "")
"DateTime64(3)"
>>> chTypeName @(DateTime64 3 "UTC")
"DateTime64(3, 'UTC')"
-}
newtype DateTime64 (precision :: Nat) (tz :: Symbol) = MkDateTime64 Word64
  deriving newtype (Int -> DateTime64 precision tz -> ShowS
[DateTime64 precision tz] -> ShowS
DateTime64 precision tz -> String
(Int -> DateTime64 precision tz -> ShowS)
-> (DateTime64 precision tz -> String)
-> ([DateTime64 precision tz] -> ShowS)
-> Show (DateTime64 precision tz)
forall (precision :: Nat) (tz :: Symbol).
Int -> DateTime64 precision tz -> ShowS
forall (precision :: Nat) (tz :: Symbol).
[DateTime64 precision tz] -> ShowS
forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall (precision :: Nat) (tz :: Symbol).
Int -> DateTime64 precision tz -> ShowS
showsPrec :: Int -> DateTime64 precision tz -> ShowS
$cshow :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> String
show :: DateTime64 precision tz -> String
$cshowList :: forall (precision :: Nat) (tz :: Symbol).
[DateTime64 precision tz] -> ShowS
showList :: [DateTime64 precision tz] -> ShowS
Show, DateTime64 precision tz -> DateTime64 precision tz -> Bool
(DateTime64 precision tz -> DateTime64 precision tz -> Bool)
-> (DateTime64 precision tz -> DateTime64 precision tz -> Bool)
-> Eq (DateTime64 precision tz)
forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> DateTime64 precision tz -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> DateTime64 precision tz -> Bool
== :: DateTime64 precision tz -> DateTime64 precision tz -> Bool
$c/= :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> DateTime64 precision tz -> Bool
/= :: DateTime64 precision tz -> DateTime64 precision tz -> Bool
Eq, Integer -> DateTime64 precision tz
DateTime64 precision tz -> DateTime64 precision tz
DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
(DateTime64 precision tz
 -> DateTime64 precision tz -> DateTime64 precision tz)
-> (DateTime64 precision tz
    -> DateTime64 precision tz -> DateTime64 precision tz)
-> (DateTime64 precision tz
    -> DateTime64 precision tz -> DateTime64 precision tz)
-> (DateTime64 precision tz -> DateTime64 precision tz)
-> (DateTime64 precision tz -> DateTime64 precision tz)
-> (DateTime64 precision tz -> DateTime64 precision tz)
-> (Integer -> DateTime64 precision tz)
-> Num (DateTime64 precision tz)
forall (precision :: Nat) (tz :: Symbol).
Integer -> DateTime64 precision tz
forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> DateTime64 precision tz
forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
+ :: DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
$c- :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
- :: DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
$c* :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
* :: DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
$cnegate :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> DateTime64 precision tz
negate :: DateTime64 precision tz -> DateTime64 precision tz
$cabs :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> DateTime64 precision tz
abs :: DateTime64 precision tz -> DateTime64 precision tz
$csignum :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> DateTime64 precision tz
signum :: DateTime64 precision tz -> DateTime64 precision tz
$cfromInteger :: forall (precision :: Nat) (tz :: Symbol).
Integer -> DateTime64 precision tz
fromInteger :: Integer -> DateTime64 precision tz
Num, Eq (DateTime64 precision tz)
DateTime64 precision tz
Eq (DateTime64 precision tz) =>
(DateTime64 precision tz
 -> DateTime64 precision tz -> DateTime64 precision tz)
-> (DateTime64 precision tz
    -> DateTime64 precision tz -> DateTime64 precision tz)
-> (DateTime64 precision tz
    -> DateTime64 precision tz -> DateTime64 precision tz)
-> (DateTime64 precision tz -> DateTime64 precision tz)
-> (DateTime64 precision tz -> Int -> DateTime64 precision tz)
-> (DateTime64 precision tz -> Int -> DateTime64 precision tz)
-> DateTime64 precision tz
-> (Int -> DateTime64 precision tz)
-> (DateTime64 precision tz -> Int -> DateTime64 precision tz)
-> (DateTime64 precision tz -> Int -> DateTime64 precision tz)
-> (DateTime64 precision tz -> Int -> DateTime64 precision tz)
-> (DateTime64 precision tz -> Int -> Bool)
-> (DateTime64 precision tz -> Maybe Int)
-> (DateTime64 precision tz -> Int)
-> (DateTime64 precision tz -> Bool)
-> (DateTime64 precision tz -> Int -> DateTime64 precision tz)
-> (DateTime64 precision tz -> Int -> DateTime64 precision tz)
-> (DateTime64 precision tz -> Int -> DateTime64 precision tz)
-> (DateTime64 precision tz -> Int -> DateTime64 precision tz)
-> (DateTime64 precision tz -> Int -> DateTime64 precision tz)
-> (DateTime64 precision tz -> Int -> DateTime64 precision tz)
-> (DateTime64 precision tz -> Int)
-> Bits (DateTime64 precision tz)
Int -> DateTime64 precision tz
DateTime64 precision tz -> Bool
DateTime64 precision tz -> Int
DateTime64 precision tz -> Maybe Int
DateTime64 precision tz -> DateTime64 precision tz
DateTime64 precision tz -> Int -> Bool
DateTime64 precision tz -> Int -> DateTime64 precision tz
DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
forall (precision :: Nat) (tz :: Symbol).
Eq (DateTime64 precision tz)
forall (precision :: Nat) (tz :: Symbol). DateTime64 precision tz
forall (precision :: Nat) (tz :: Symbol).
Int -> DateTime64 precision tz
forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> Bool
forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> Int
forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> Maybe Int
forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> DateTime64 precision tz
forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> Int -> Bool
forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> Int -> DateTime64 precision tz
forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
$c.&. :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
.&. :: DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
$c.|. :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
.|. :: DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
$cxor :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
xor :: DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
$ccomplement :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> DateTime64 precision tz
complement :: DateTime64 precision tz -> DateTime64 precision tz
$cshift :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> Int -> DateTime64 precision tz
shift :: DateTime64 precision tz -> Int -> DateTime64 precision tz
$crotate :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> Int -> DateTime64 precision tz
rotate :: DateTime64 precision tz -> Int -> DateTime64 precision tz
$czeroBits :: forall (precision :: Nat) (tz :: Symbol). DateTime64 precision tz
zeroBits :: DateTime64 precision tz
$cbit :: forall (precision :: Nat) (tz :: Symbol).
Int -> DateTime64 precision tz
bit :: Int -> DateTime64 precision tz
$csetBit :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> Int -> DateTime64 precision tz
setBit :: DateTime64 precision tz -> Int -> DateTime64 precision tz
$cclearBit :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> Int -> DateTime64 precision tz
clearBit :: DateTime64 precision tz -> Int -> DateTime64 precision tz
$ccomplementBit :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> Int -> DateTime64 precision tz
complementBit :: DateTime64 precision tz -> Int -> DateTime64 precision tz
$ctestBit :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> Int -> Bool
testBit :: DateTime64 precision tz -> Int -> Bool
$cbitSizeMaybe :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> Maybe Int
bitSizeMaybe :: DateTime64 precision tz -> Maybe Int
$cbitSize :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> Int
bitSize :: DateTime64 precision tz -> Int
$cisSigned :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> Bool
isSigned :: DateTime64 precision tz -> Bool
$cshiftL :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> Int -> DateTime64 precision tz
shiftL :: DateTime64 precision tz -> Int -> DateTime64 precision tz
$cunsafeShiftL :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> Int -> DateTime64 precision tz
unsafeShiftL :: DateTime64 precision tz -> Int -> DateTime64 precision tz
$cshiftR :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> Int -> DateTime64 precision tz
shiftR :: DateTime64 precision tz -> Int -> DateTime64 precision tz
$cunsafeShiftR :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> Int -> DateTime64 precision tz
unsafeShiftR :: DateTime64 precision tz -> Int -> DateTime64 precision tz
$crotateL :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> Int -> DateTime64 precision tz
rotateL :: DateTime64 precision tz -> Int -> DateTime64 precision tz
$crotateR :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> Int -> DateTime64 precision tz
rotateR :: DateTime64 precision tz -> Int -> DateTime64 precision tz
$cpopCount :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> Int
popCount :: DateTime64 precision tz -> Int
Bits, Int -> DateTime64 precision tz
DateTime64 precision tz -> Int
DateTime64 precision tz -> [DateTime64 precision tz]
DateTime64 precision tz -> DateTime64 precision tz
DateTime64 precision tz
-> DateTime64 precision tz -> [DateTime64 precision tz]
DateTime64 precision tz
-> DateTime64 precision tz
-> DateTime64 precision tz
-> [DateTime64 precision tz]
(DateTime64 precision tz -> DateTime64 precision tz)
-> (DateTime64 precision tz -> DateTime64 precision tz)
-> (Int -> DateTime64 precision tz)
-> (DateTime64 precision tz -> Int)
-> (DateTime64 precision tz -> [DateTime64 precision tz])
-> (DateTime64 precision tz
    -> DateTime64 precision tz -> [DateTime64 precision tz])
-> (DateTime64 precision tz
    -> DateTime64 precision tz -> [DateTime64 precision tz])
-> (DateTime64 precision tz
    -> DateTime64 precision tz
    -> DateTime64 precision tz
    -> [DateTime64 precision tz])
-> Enum (DateTime64 precision tz)
forall (precision :: Nat) (tz :: Symbol).
Int -> DateTime64 precision tz
forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> Int
forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> [DateTime64 precision tz]
forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> DateTime64 precision tz
forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz
-> DateTime64 precision tz -> [DateTime64 precision tz]
forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz
-> DateTime64 precision tz
-> DateTime64 precision tz
-> [DateTime64 precision tz]
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 :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> DateTime64 precision tz
succ :: DateTime64 precision tz -> DateTime64 precision tz
$cpred :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> DateTime64 precision tz
pred :: DateTime64 precision tz -> DateTime64 precision tz
$ctoEnum :: forall (precision :: Nat) (tz :: Symbol).
Int -> DateTime64 precision tz
toEnum :: Int -> DateTime64 precision tz
$cfromEnum :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> Int
fromEnum :: DateTime64 precision tz -> Int
$cenumFrom :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> [DateTime64 precision tz]
enumFrom :: DateTime64 precision tz -> [DateTime64 precision tz]
$cenumFromThen :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz
-> DateTime64 precision tz -> [DateTime64 precision tz]
enumFromThen :: DateTime64 precision tz
-> DateTime64 precision tz -> [DateTime64 precision tz]
$cenumFromTo :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz
-> DateTime64 precision tz -> [DateTime64 precision tz]
enumFromTo :: DateTime64 precision tz
-> DateTime64 precision tz -> [DateTime64 precision tz]
$cenumFromThenTo :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz
-> DateTime64 precision tz
-> DateTime64 precision tz
-> [DateTime64 precision tz]
enumFromThenTo :: DateTime64 precision tz
-> DateTime64 precision tz
-> DateTime64 precision tz
-> [DateTime64 precision tz]
Enum, Eq (DateTime64 precision tz)
Eq (DateTime64 precision tz) =>
(DateTime64 precision tz -> DateTime64 precision tz -> Ordering)
-> (DateTime64 precision tz -> DateTime64 precision tz -> Bool)
-> (DateTime64 precision tz -> DateTime64 precision tz -> Bool)
-> (DateTime64 precision tz -> DateTime64 precision tz -> Bool)
-> (DateTime64 precision tz -> DateTime64 precision tz -> Bool)
-> (DateTime64 precision tz
    -> DateTime64 precision tz -> DateTime64 precision tz)
-> (DateTime64 precision tz
    -> DateTime64 precision tz -> DateTime64 precision tz)
-> Ord (DateTime64 precision tz)
DateTime64 precision tz -> DateTime64 precision tz -> Bool
DateTime64 precision tz -> DateTime64 precision tz -> Ordering
DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
forall (precision :: Nat) (tz :: Symbol).
Eq (DateTime64 precision tz)
forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> DateTime64 precision tz -> Bool
forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> DateTime64 precision tz -> Ordering
forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> DateTime64 precision tz -> Ordering
compare :: DateTime64 precision tz -> DateTime64 precision tz -> Ordering
$c< :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> DateTime64 precision tz -> Bool
< :: DateTime64 precision tz -> DateTime64 precision tz -> Bool
$c<= :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> DateTime64 precision tz -> Bool
<= :: DateTime64 precision tz -> DateTime64 precision tz -> Bool
$c> :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> DateTime64 precision tz -> Bool
> :: DateTime64 precision tz -> DateTime64 precision tz -> Bool
$c>= :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> DateTime64 precision tz -> Bool
>= :: DateTime64 precision tz -> DateTime64 precision tz -> Bool
$cmax :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
max :: DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
$cmin :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
min :: DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
Ord, Num (DateTime64 precision tz)
Ord (DateTime64 precision tz)
(Num (DateTime64 precision tz), Ord (DateTime64 precision tz)) =>
(DateTime64 precision tz -> Rational)
-> Real (DateTime64 precision tz)
DateTime64 precision tz -> Rational
forall (precision :: Nat) (tz :: Symbol).
Num (DateTime64 precision tz)
forall (precision :: Nat) (tz :: Symbol).
Ord (DateTime64 precision tz)
forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> Rational
toRational :: DateTime64 precision tz -> Rational
Real, Enum (DateTime64 precision tz)
Real (DateTime64 precision tz)
(Real (DateTime64 precision tz), Enum (DateTime64 precision tz)) =>
(DateTime64 precision tz
 -> DateTime64 precision tz -> DateTime64 precision tz)
-> (DateTime64 precision tz
    -> DateTime64 precision tz -> DateTime64 precision tz)
-> (DateTime64 precision tz
    -> DateTime64 precision tz -> DateTime64 precision tz)
-> (DateTime64 precision tz
    -> DateTime64 precision tz -> DateTime64 precision tz)
-> (DateTime64 precision tz
    -> DateTime64 precision tz
    -> (DateTime64 precision tz, DateTime64 precision tz))
-> (DateTime64 precision tz
    -> DateTime64 precision tz
    -> (DateTime64 precision tz, DateTime64 precision tz))
-> (DateTime64 precision tz -> Integer)
-> Integral (DateTime64 precision tz)
DateTime64 precision tz -> Integer
DateTime64 precision tz
-> DateTime64 precision tz
-> (DateTime64 precision tz, DateTime64 precision tz)
DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
forall (precision :: Nat) (tz :: Symbol).
Enum (DateTime64 precision tz)
forall (precision :: Nat) (tz :: Symbol).
Real (DateTime64 precision tz)
forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> Integer
forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz
-> DateTime64 precision tz
-> (DateTime64 precision tz, DateTime64 precision tz)
forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
quot :: DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
$crem :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
rem :: DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
$cdiv :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
div :: DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
$cmod :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
mod :: DateTime64 precision tz
-> DateTime64 precision tz -> DateTime64 precision tz
$cquotRem :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz
-> DateTime64 precision tz
-> (DateTime64 precision tz, DateTime64 precision tz)
quotRem :: DateTime64 precision tz
-> DateTime64 precision tz
-> (DateTime64 precision tz, DateTime64 precision tz)
$cdivMod :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz
-> DateTime64 precision tz
-> (DateTime64 precision tz, DateTime64 precision tz)
divMod :: DateTime64 precision tz
-> DateTime64 precision tz
-> (DateTime64 precision tz, DateTime64 precision tz)
$ctoInteger :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> Integer
toInteger :: DateTime64 precision tz -> Integer
Integral, DateTime64 precision tz
DateTime64 precision tz
-> DateTime64 precision tz -> Bounded (DateTime64 precision tz)
forall (precision :: Nat) (tz :: Symbol). DateTime64 precision tz
forall a. a -> a -> Bounded a
$cminBound :: forall (precision :: Nat) (tz :: Symbol). DateTime64 precision tz
minBound :: DateTime64 precision tz
$cmaxBound :: forall (precision :: Nat) (tz :: Symbol). DateTime64 precision tz
maxBound :: DateTime64 precision tz
Bounded, DateTime64 precision tz -> ()
(DateTime64 precision tz -> ()) -> NFData (DateTime64 precision tz)
forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall (precision :: Nat) (tz :: Symbol).
DateTime64 precision tz -> ()
rnf :: DateTime64 precision tz -> ()
NFData)

instance
  (KnownSymbol tz, KnownNat precision)
  =>
  IsChType (DateTime64 precision tz)
  where
  chTypeName :: String
chTypeName =
    let
      prec :: String
prec = Integer -> String
forall a. Show a => a -> String
show (forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal @precision Proxy precision
forall {k} (t :: k). Proxy t
Proxy)
    in
    case forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal @tz Proxy tz
forall {k} (t :: k). Proxy t
Proxy of
      String
"" -> String
"DateTime64(" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
prec String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
")"
      String
tz -> String
"DateTime64(" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
prec String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
", '" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
tz String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"')"
  defaultValueOfTypeName :: DateTime64 precision tz
defaultValueOfTypeName = UInt64 -> DateTime64 precision tz
forall (precision :: Nat) (tz :: Symbol).
UInt64 -> DateTime64 precision tz
MkDateTime64 UInt64
0


-- | ClickHouse Array column type
newtype Array a = MkChArray [a]
  deriving newtype (Int -> Array a -> ShowS
[Array a] -> ShowS
Array a -> String
(Int -> Array a -> ShowS)
-> (Array a -> String) -> ([Array a] -> ShowS) -> Show (Array a)
forall a. Show a => Int -> Array a -> ShowS
forall a. Show a => [Array a] -> ShowS
forall a. Show a => Array a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> Array a -> ShowS
showsPrec :: Int -> Array a -> ShowS
$cshow :: forall a. Show a => Array a -> String
show :: Array a -> String
$cshowList :: forall a. Show a => [Array a] -> ShowS
showList :: [Array a] -> ShowS
Show, Array a -> Array a -> Bool
(Array a -> Array a -> Bool)
-> (Array a -> Array a -> Bool) -> Eq (Array a)
forall a. Eq a => Array a -> Array a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => Array a -> Array a -> Bool
== :: Array a -> Array a -> Bool
$c/= :: forall a. Eq a => Array a -> Array a -> Bool
/= :: Array a -> Array a -> Bool
Eq, Array a -> ()
(Array a -> ()) -> NFData (Array a)
forall a. NFData a => Array a -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall a. NFData a => Array a -> ()
rnf :: Array a -> ()
NFData)
instance IsChType chType => IsChType (Array chType)
  where
  chTypeName :: String
chTypeName = String
"Array(" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> forall chType. IsChType chType => String
chTypeName @chType String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
")"
  defaultValueOfTypeName :: Array chType
defaultValueOfTypeName = [chType] -> Array chType
forall a. [a] -> Array a
MkChArray []

-- | ClickHouse LowCardinality(T) column type
newtype LowCardinality chType = MkLowCardinality chType
instance IsLowCardinalitySupported chType => IsChType (LowCardinality chType)
  where
  chTypeName :: String
chTypeName = String
"LowCardinality(" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> forall chType. IsChType chType => String
chTypeName @chType String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
")"
  defaultValueOfTypeName :: LowCardinality chType
defaultValueOfTypeName = chType -> LowCardinality chType
forall chType. chType -> LowCardinality chType
MkLowCardinality (chType -> LowCardinality chType)
-> chType -> LowCardinality chType
forall a b. (a -> b) -> a -> b
$ forall chType. IsChType chType => chType
defaultValueOfTypeName @chType

deriving newtype instance (Eq chType, IsLowCardinalitySupported chType) => Eq (LowCardinality chType)
deriving newtype instance (NFData chType, IsLowCardinalitySupported chType) => NFData (LowCardinality chType)
deriving newtype instance IsString (LowCardinality ChString)

class IsChType chType => IsLowCardinalitySupported chType
instance IsLowCardinalitySupported ChString
instance
  ( IsLowCardinalitySupported chType
  , IsChType (Nullable chType)
  ) =>
  IsLowCardinalitySupported (Nullable chType)

instance {-# OVERLAPPABLE #-}
  ( IsChType chType
  , TypeError
    (    'Text "LowCardinality("  ':<>: 'ShowType chType  ':<>: 'Text ") is unsupported"
    ':$$: 'Text "Use one of these types:"
    ':$$: 'Text "  ChString"
    ':$$: 'Text "  DateTime"
    ':$$: 'Text "  Nullable(T)"
    )
  ) => IsLowCardinalitySupported chType








-- * Serialization

-- *** Generic API

class Serializable chType
  where
  default serialize :: (Generic chType, GSerial (Rep chType)) => ProtocolRevision -> chType -> Builder
  serialize :: ProtocolRevision -> chType -> Builder
  serialize ProtocolRevision
rev = ProtocolRevision -> Rep chType Any -> Builder
forall p. ProtocolRevision -> Rep chType p -> Builder
forall (f :: * -> *) p.
GSerial f =>
ProtocolRevision -> f p -> Builder
gSerialize ProtocolRevision
rev (Rep chType Any -> Builder)
-> (chType -> Rep chType Any) -> chType -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. chType -> Rep chType Any
forall x. chType -> Rep chType x
forall a x. Generic a => a -> Rep a x
from

class
  Deserializable chType
  where
  {-# INLINE deserialize #-}
  default deserialize :: (Generic chType, GDeserial (Rep chType)) => ProtocolRevision -> Get chType
  deserialize :: ProtocolRevision -> Get chType
  deserialize ProtocolRevision
rev = Rep chType Any -> chType
forall a x. Generic a => Rep a x -> a
forall x. Rep chType x -> chType
to (Rep chType Any -> chType) -> Get (Rep chType Any) -> Get chType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ProtocolRevision -> Get (Rep chType Any)
forall p. ProtocolRevision -> Get (Rep chType p)
forall (f :: * -> *) p.
GDeserial f =>
ProtocolRevision -> Get (f p)
gDeserialize ProtocolRevision
rev


{-# INLINE replicateGet #-}
replicateGet :: UVarInt -> Get chType -> Get [chType]
replicateGet :: forall chType. UVarInt -> Get chType -> Get [chType]
replicateGet UVarInt
cnt0 Get chType
f = UVarInt -> Get [chType]
loop UVarInt
cnt0
  where
  loop :: UVarInt -> Get [chType]
loop UVarInt
cnt
    | UVarInt
cnt UVarInt -> UVarInt -> Bool
forall a. Ord a => a -> a -> Bool
<= UVarInt
0  = [chType] -> Get [chType]
forall a. a -> Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
    | Bool
otherwise = (chType -> [chType] -> [chType])
-> Get chType -> Get [chType] -> Get [chType]
forall a b c. (a -> b -> c) -> Get a -> Get b -> Get c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (:) Get chType
f (UVarInt -> Get [chType]
loop (UVarInt
cnt UVarInt -> UVarInt -> UVarInt
forall a. Num a => a -> a -> a
- UVarInt
1))

instance Serializable UVarInt where
  serialize :: ProtocolRevision -> UVarInt -> Builder
serialize ProtocolRevision
_ = UVarInt -> Builder
forall {t}. (Integral t, Bits t) => t -> Builder
go
    where
    go :: t -> Builder
go t
i
      | t
i t -> t -> Bool
forall a. Ord a => a -> a -> Bool
< t
0x80 = UInt8 -> Builder
word8 (t -> UInt8
forall a b. (Integral a, Num b) => a -> b
fromIntegral t
i)
      | Bool
otherwise = UInt8 -> Builder
word8 (UInt8 -> Int -> UInt8
forall a. Bits a => a -> Int -> a
setBit (t -> UInt8
forall a b. (Integral a, Num b) => a -> b
fromIntegral t
i) Int
7) Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> t -> Builder
go (t
i t -> Int -> t
forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
7)
instance Serializable ChString where
  serialize :: ProtocolRevision -> ChString -> Builder
serialize ProtocolRevision
rev (MkChString ByteString
str) = (forall chType.
Serializable chType =>
ProtocolRevision -> chType -> Builder
serialize @UVarInt ProtocolRevision
rev (UVarInt -> Builder)
-> (ByteString -> UVarInt) -> ByteString -> 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) -> (ByteString -> Int) -> ByteString -> UVarInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Int
BS.length) ByteString
str Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> ByteString -> Builder
byteString ByteString
str
instance Serializable UUID where serialize :: ProtocolRevision -> UUID -> Builder
serialize ProtocolRevision
_ = (\(MkUUID (Word128 UInt64
hi UInt64
lo)) -> UInt64 -> Builder
word64LE UInt64
lo Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> UInt64 -> Builder
word64LE UInt64
hi)
instance Serializable Int8 where serialize :: ProtocolRevision -> Int8 -> Builder
serialize ProtocolRevision
_ = Int8 -> Builder
int8 
instance Serializable Int16 where serialize :: ProtocolRevision -> Int16 -> Builder
serialize ProtocolRevision
_ = Int16 -> Builder
int16LE
instance Serializable Int32 where serialize :: ProtocolRevision -> Int32 -> Builder
serialize ProtocolRevision
_ = Int32 -> Builder
int32LE
instance Serializable Int64 where serialize :: ProtocolRevision -> Int64 -> Builder
serialize ProtocolRevision
_ = Int64 -> Builder
int64LE
instance Serializable Int128 where serialize :: ProtocolRevision -> Int128 -> Builder
serialize ProtocolRevision
_ = (\(Int128 UInt64
hi UInt64
lo) -> UInt64 -> Builder
word64LE UInt64
lo Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> UInt64 -> Builder
word64LE UInt64
hi)
instance Serializable UInt8 where serialize :: ProtocolRevision -> UInt8 -> Builder
serialize ProtocolRevision
_ = UInt8 -> Builder
word8
instance Serializable UInt16 where serialize :: ProtocolRevision -> UInt16 -> Builder
serialize ProtocolRevision
_ = UInt16 -> Builder
word16LE
instance Serializable UInt32 where serialize :: ProtocolRevision -> UInt32 -> Builder
serialize ProtocolRevision
_ = UInt32 -> Builder
word32LE
instance Serializable UInt64 where serialize :: ProtocolRevision -> UInt64 -> Builder
serialize ProtocolRevision
_ = UInt64 -> Builder
word64LE
instance Serializable UInt128 where serialize :: ProtocolRevision -> UInt128 -> Builder
serialize ProtocolRevision
_ = (\(Word128 UInt64
hi UInt64
lo) -> UInt64 -> Builder
word64LE UInt64
lo Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> UInt64 -> Builder
word64LE UInt64
hi)
instance Serializable (DateTime tz) where serialize :: ProtocolRevision -> DateTime tz -> Builder
serialize ProtocolRevision
_ (MkDateTime UInt32
w32) = UInt32 -> Builder
word32LE UInt32
w32
instance Serializable (DateTime64 precision tz) where serialize :: ProtocolRevision -> DateTime64 precision tz -> Builder
serialize ProtocolRevision
_ (MkDateTime64 UInt64
w64) = UInt64 -> Builder
word64LE UInt64
w64
instance Serializable Date where serialize :: ProtocolRevision -> Date -> Builder
serialize ProtocolRevision
_ (MkDate UInt16
w16) = UInt16 -> Builder
word16LE UInt16
w16


instance Deserializable Int8 where deserialize :: ProtocolRevision -> Get Int8
deserialize ProtocolRevision
_ = Get Int8
getInt8; {-# INLINE deserialize #-}
instance Deserializable Int16 where deserialize :: ProtocolRevision -> Get Int16
deserialize ProtocolRevision
_ = Get Int16
getInt16le; {-# INLINE deserialize #-}
instance Deserializable Int32 where deserialize :: ProtocolRevision -> Get Int32
deserialize ProtocolRevision
_ = Get Int32
getInt32le; {-# INLINE deserialize #-}
instance Deserializable Int64 where deserialize :: ProtocolRevision -> Get Int64
deserialize ProtocolRevision
_ = Get Int64
getInt64le; {-# INLINE deserialize #-}
instance Deserializable Int128 where
  deserialize :: ProtocolRevision -> Get Int128
deserialize ProtocolRevision
_ = do
    UInt64
low <- Get UInt64
getWord64le
    UInt64
high <- Get UInt64
getWord64le
    Int128 -> Get Int128
forall a. a -> Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int128 -> Get Int128) -> Int128 -> Get Int128
forall a b. (a -> b) -> a -> b
$ UInt64 -> UInt64 -> Int128
Int128 UInt64
high UInt64
low
  {-# INLINE deserialize #-}
instance Deserializable UInt8 where deserialize :: ProtocolRevision -> Get UInt8
deserialize ProtocolRevision
_ = Get UInt8
getWord8; {-# INLINE deserialize #-}
instance Deserializable UInt16 where deserialize :: ProtocolRevision -> Get UInt16
deserialize ProtocolRevision
_ = Get UInt16
getWord16le; {-# INLINE deserialize #-}
instance Deserializable UInt32 where deserialize :: ProtocolRevision -> Get UInt32
deserialize ProtocolRevision
_ = Get UInt32
getWord32le; {-# INLINE deserialize #-}
instance Deserializable UInt64 where deserialize :: ProtocolRevision -> Get UInt64
deserialize ProtocolRevision
_ = Get UInt64
getWord64le; {-# INLINE deserialize #-}
instance Deserializable UInt128 where
  deserialize :: ProtocolRevision -> Get UInt128
deserialize ProtocolRevision
_ = do
    UInt64
low <- Get UInt64
getWord64le
    UInt64
high <- Get UInt64
getWord64le
    UInt128 -> Get UInt128
forall a. a -> Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UInt128 -> Get UInt128) -> UInt128 -> Get UInt128
forall a b. (a -> b) -> a -> b
$ UInt64 -> UInt64 -> UInt128
Word128 UInt64
high UInt64
low
  {-# INLINE deserialize #-}
instance Deserializable UUID where
  deserialize :: ProtocolRevision -> Get UUID
deserialize ProtocolRevision
_ = do
    UInt64
low <- Get UInt64
getWord64le
    UInt64
high <- Get UInt64
getWord64le
    UUID -> Get UUID
forall a. a -> Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UUID -> Get UUID) -> UUID -> Get UUID
forall a b. (a -> b) -> a -> b
$ UInt128 -> UUID
MkUUID (UInt64 -> UInt64 -> UInt128
Word128 UInt64
high UInt64
low)
  {-# INLINE deserialize #-}
instance Deserializable Date where deserialize :: ProtocolRevision -> Get Date
deserialize ProtocolRevision
_ = UInt16 -> Date
MkDate (UInt16 -> Date) -> Get UInt16 -> Get Date
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get UInt16
getWord16le; {-# INLINE deserialize #-}
instance Deserializable (DateTime tz) where deserialize :: ProtocolRevision -> Get (DateTime tz)
deserialize ProtocolRevision
_ = UInt32 -> DateTime tz
forall (tz :: Symbol). UInt32 -> DateTime tz
MkDateTime (UInt32 -> DateTime tz) -> Get UInt32 -> Get (DateTime tz)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get UInt32
getWord32le; {-# INLINE deserialize #-}
instance Deserializable (DateTime64 precision tz) where deserialize :: ProtocolRevision -> Get (DateTime64 precision tz)
deserialize ProtocolRevision
_ = UInt64 -> DateTime64 precision tz
forall (precision :: Nat) (tz :: Symbol).
UInt64 -> DateTime64 precision tz
MkDateTime64 (UInt64 -> DateTime64 precision tz)
-> Get UInt64 -> Get (DateTime64 precision tz)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get UInt64
getWord64le; {-# INLINE deserialize #-}
instance Deserializable ChString where
  {-# INLINE deserialize #-}
  deserialize :: ProtocolRevision -> Get ChString
deserialize = (ByteString -> ChString) -> Get ByteString -> Get ChString
forall a b. (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> ChString
MkChString (Get ByteString -> Get ChString)
-> (UVarInt -> Get ByteString) -> UVarInt -> Get ChString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Get ByteString
getByteString (Int -> Get ByteString)
-> (UVarInt -> Int) -> UVarInt -> Get ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UVarInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (UVarInt -> Get ChString)
-> (ProtocolRevision -> Get UVarInt)
-> ProtocolRevision
-> Get ChString
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< forall chType.
Deserializable chType =>
ProtocolRevision -> Get chType
deserialize @UVarInt
instance Deserializable UVarInt where
  {-# INLINE deserialize #-}
  deserialize :: ProtocolRevision -> Get UVarInt
deserialize ProtocolRevision
_ = Int -> UVarInt -> Get UVarInt
forall {a}. (Bits a, Num a) => Int -> a -> Get a
go Int
0 (UVarInt
0 :: UVarInt)
    where
    go :: Int -> a -> Get a
go Int
i a
o | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
10 = do
      UInt8
byte <- Get UInt8
getWord8
      let o' :: a
o' = a
o a -> a -> a
forall a. Bits a => a -> a -> a
.|. ((UInt8 -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral UInt8
byte a -> a -> a
forall a. Bits a => a -> a -> a
.&. a
0x7f) a -> Int -> a
forall a. Bits a => a -> Int -> a
`unsafeShiftL` (Int
7 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
i))
      if UInt8
byte UInt8 -> UInt8 -> UInt8
forall a. Bits a => a -> a -> a
.&. UInt8
0x80 UInt8 -> UInt8 -> Bool
forall a. Eq a => a -> a -> Bool
== UInt8
0 then a -> Get a
forall a. a -> Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> Get a) -> a -> Get a
forall a b. (a -> b) -> a -> b
$! a
o' else Int -> a -> Get a
go (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (a -> Get a) -> a -> Get a
forall a b. (a -> b) -> a -> b
$! a
o'
    go Int
_ a
_ = String -> Get a
forall a. String -> Get a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"input exceeds varuint size"
instance Deserializable prim => Deserializable [prim] where
  deserialize :: ProtocolRevision -> Get [prim]
deserialize ProtocolRevision
rev = do
    UVarInt
len <- forall chType.
Deserializable chType =>
ProtocolRevision -> Get chType
deserialize @UVarInt ProtocolRevision
rev
    UVarInt -> Get prim -> Get [prim]
forall chType. UVarInt -> Get chType -> Get [chType]
replicateGet UVarInt
len (forall chType.
Deserializable chType =>
ProtocolRevision -> Get chType
deserialize @prim ProtocolRevision
rev)

-- ** Generics

class GSerial f where
  gSerialize :: ProtocolRevision -> f p -> Builder

instance GSerial f => GSerial (D1 c (C1 c2 f)) where
  gSerialize :: forall p. ProtocolRevision -> D1 c (C1 c2 f) p -> Builder
gSerialize ProtocolRevision
rev (M1 (M1 f p
re)) = ProtocolRevision -> f p -> Builder
forall p. ProtocolRevision -> f p -> Builder
forall (f :: * -> *) p.
GSerial f =>
ProtocolRevision -> f p -> Builder
gSerialize ProtocolRevision
rev f p
re
  {-# INLINE gSerialize #-}

instance (GSerial left1,  GSerial right) => GSerial (left1 :*: right) where
  gSerialize :: forall p. ProtocolRevision -> (:*:) left1 right p -> Builder
gSerialize ProtocolRevision
rev (left1 p
l :*: right p
r) = ProtocolRevision -> left1 p -> Builder
forall p. ProtocolRevision -> left1 p -> Builder
forall (f :: * -> *) p.
GSerial f =>
ProtocolRevision -> f p -> Builder
gSerialize ProtocolRevision
rev left1 p
l Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> ProtocolRevision -> right p -> Builder
forall p. ProtocolRevision -> right p -> Builder
forall (f :: * -> *) p.
GSerial f =>
ProtocolRevision -> f p -> Builder
gSerialize ProtocolRevision
rev right p
r
  {-# INLINE gSerialize #-}

instance Serializable chType => GSerial (S1 metaSel (Rec0 chType)) where
  gSerialize :: forall p. ProtocolRevision -> S1 metaSel (Rec0 chType) p -> Builder
gSerialize ProtocolRevision
rev (M1 (K1 chType
re)) = ProtocolRevision -> chType -> Builder
forall chType.
Serializable chType =>
ProtocolRevision -> chType -> Builder
serialize ProtocolRevision
rev chType
re
  {-# INLINE gSerialize #-}

class GDeserial f
  where
  gDeserialize :: ProtocolRevision -> Get (f p)

instance GDeserial f => GDeserial (D1 c (C1 c2 f))
  where
  gDeserialize :: forall p. ProtocolRevision -> Get (D1 c (C1 c2 f) p)
gDeserialize ProtocolRevision
rev = C1 c2 f p -> M1 D c (C1 c2 f) p
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 (C1 c2 f p -> M1 D c (C1 c2 f) p)
-> (f p -> C1 c2 f p) -> f p -> M1 D c (C1 c2 f) p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f p -> C1 c2 f p
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 (f p -> M1 D c (C1 c2 f) p)
-> Get (f p) -> Get (M1 D c (C1 c2 f) p)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ProtocolRevision -> Get (f p)
forall p. ProtocolRevision -> Get (f p)
forall (f :: * -> *) p.
GDeserial f =>
ProtocolRevision -> Get (f p)
gDeserialize ProtocolRevision
rev
  {-# INLINE gDeserialize #-}

instance (GDeserial left, GDeserial right) => GDeserial (left :*: right) where
  gDeserialize :: forall p. ProtocolRevision -> Get ((:*:) left right p)
gDeserialize ProtocolRevision
rev = do
    (left p -> right p -> (:*:) left right p)
-> Get (left p) -> Get (right p) -> Get ((:*:) left right p)
forall a b c. (a -> b -> c) -> Get a -> Get b -> Get c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 left p -> right p -> (:*:) left right p
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
(:*:)
      (ProtocolRevision -> Get (left p)
forall p. ProtocolRevision -> Get (left p)
forall (f :: * -> *) p.
GDeserial f =>
ProtocolRevision -> Get (f p)
gDeserialize ProtocolRevision
rev)
      (ProtocolRevision -> Get (right p)
forall p. ProtocolRevision -> Get (right p)
forall (f :: * -> *) p.
GDeserial f =>
ProtocolRevision -> Get (f p)
gDeserialize ProtocolRevision
rev)
  {-# INLINE gDeserialize #-}

instance {-# OVERLAPPING #-}
  GDeserial right => GDeserial (S1 metaSel (Rec0 ProtocolRevision) :*: right) where
  gDeserialize :: forall p.
ProtocolRevision
-> Get ((:*:) (S1 metaSel (Rec0 ProtocolRevision)) right p)
gDeserialize ProtocolRevision
rev = do
    ProtocolRevision
chosenRev <- ProtocolRevision -> ProtocolRevision -> ProtocolRevision
forall a. Ord a => a -> a -> a
min ProtocolRevision
rev (ProtocolRevision -> ProtocolRevision)
-> (UVarInt -> ProtocolRevision) -> UVarInt -> ProtocolRevision
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UVarInt -> ProtocolRevision
forall a b. Coercible a b => a -> b
coerce (UVarInt -> ProtocolRevision)
-> Get UVarInt -> Get ProtocolRevision
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall chType.
Deserializable chType =>
ProtocolRevision -> Get chType
deserialize @UVarInt ProtocolRevision
rev
    (S1 metaSel (Rec0 ProtocolRevision) p
 -> right p -> (:*:) (S1 metaSel (Rec0 ProtocolRevision)) right p)
-> Get (S1 metaSel (Rec0 ProtocolRevision) p)
-> Get (right p)
-> Get ((:*:) (S1 metaSel (Rec0 ProtocolRevision)) right p)
forall a b c. (a -> b -> c) -> Get a -> Get b -> Get c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 S1 metaSel (Rec0 ProtocolRevision) p
-> right p -> (:*:) (S1 metaSel (Rec0 ProtocolRevision)) right p
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
(:*:)
      (S1 metaSel (Rec0 ProtocolRevision) p
-> Get (S1 metaSel (Rec0 ProtocolRevision) p)
forall a. a -> Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (S1 metaSel (Rec0 ProtocolRevision) p
 -> Get (S1 metaSel (Rec0 ProtocolRevision) p))
-> (ProtocolRevision -> S1 metaSel (Rec0 ProtocolRevision) p)
-> ProtocolRevision
-> Get (S1 metaSel (Rec0 ProtocolRevision) p)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rec0 ProtocolRevision p -> S1 metaSel (Rec0 ProtocolRevision) p
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 (Rec0 ProtocolRevision p -> S1 metaSel (Rec0 ProtocolRevision) p)
-> (ProtocolRevision -> Rec0 ProtocolRevision p)
-> ProtocolRevision
-> S1 metaSel (Rec0 ProtocolRevision) p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProtocolRevision -> Rec0 ProtocolRevision p
forall k i c (p :: k). c -> K1 i c p
K1 (ProtocolRevision -> Get (S1 metaSel (Rec0 ProtocolRevision) p))
-> ProtocolRevision -> Get (S1 metaSel (Rec0 ProtocolRevision) p)
forall a b. (a -> b) -> a -> b
$ ProtocolRevision
chosenRev)
      (forall (f :: * -> *) p.
GDeserial f =>
ProtocolRevision -> Get (f p)
gDeserialize @right ProtocolRevision
chosenRev)
  {-# INLINE gDeserialize #-}

instance
  Deserializable chType
  =>
  GDeserial (S1 metaSel (Rec0 chType))
  where
  {-# INLINE gDeserialize #-}
  gDeserialize :: forall p. ProtocolRevision -> Get (S1 metaSel (Rec0 chType) p)
gDeserialize ProtocolRevision
rev = Rec0 chType p -> M1 S metaSel (Rec0 chType) p
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 (Rec0 chType p -> M1 S metaSel (Rec0 chType) p)
-> (chType -> Rec0 chType p)
-> chType
-> M1 S metaSel (Rec0 chType) p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. chType -> Rec0 chType p
forall k i c (p :: k). c -> K1 i c p
K1 (chType -> M1 S metaSel (Rec0 chType) p)
-> Get chType -> Get (M1 S metaSel (Rec0 chType) p)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall chType.
Deserializable chType =>
ProtocolRevision -> Get chType
deserialize @chType ProtocolRevision
rev 







-- * Protocol parts

{- |
  Unsigned variable-length quantity encoding
  
  Part of protocol implementation
-}
newtype UVarInt = MkUVarInt Word64
  deriving newtype (Int -> UVarInt -> ShowS
[UVarInt] -> ShowS
UVarInt -> String
(Int -> UVarInt -> ShowS)
-> (UVarInt -> String) -> ([UVarInt] -> ShowS) -> Show UVarInt
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UVarInt -> ShowS
showsPrec :: Int -> UVarInt -> ShowS
$cshow :: UVarInt -> String
show :: UVarInt -> String
$cshowList :: [UVarInt] -> ShowS
showList :: [UVarInt] -> ShowS
Show, UVarInt -> UVarInt -> Bool
(UVarInt -> UVarInt -> Bool)
-> (UVarInt -> UVarInt -> Bool) -> Eq UVarInt
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UVarInt -> UVarInt -> Bool
== :: UVarInt -> UVarInt -> Bool
$c/= :: UVarInt -> UVarInt -> Bool
/= :: UVarInt -> UVarInt -> Bool
Eq, Integer -> UVarInt
UVarInt -> UVarInt
UVarInt -> UVarInt -> UVarInt
(UVarInt -> UVarInt -> UVarInt)
-> (UVarInt -> UVarInt -> UVarInt)
-> (UVarInt -> UVarInt -> UVarInt)
-> (UVarInt -> UVarInt)
-> (UVarInt -> UVarInt)
-> (UVarInt -> UVarInt)
-> (Integer -> UVarInt)
-> Num UVarInt
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: UVarInt -> UVarInt -> UVarInt
+ :: UVarInt -> UVarInt -> UVarInt
$c- :: UVarInt -> UVarInt -> UVarInt
- :: UVarInt -> UVarInt -> UVarInt
$c* :: UVarInt -> UVarInt -> UVarInt
* :: UVarInt -> UVarInt -> UVarInt
$cnegate :: UVarInt -> UVarInt
negate :: UVarInt -> UVarInt
$cabs :: UVarInt -> UVarInt
abs :: UVarInt -> UVarInt
$csignum :: UVarInt -> UVarInt
signum :: UVarInt -> UVarInt
$cfromInteger :: Integer -> UVarInt
fromInteger :: Integer -> UVarInt
Num, Eq UVarInt
UVarInt
Eq UVarInt =>
(UVarInt -> UVarInt -> UVarInt)
-> (UVarInt -> UVarInt -> UVarInt)
-> (UVarInt -> UVarInt -> UVarInt)
-> (UVarInt -> UVarInt)
-> (UVarInt -> Int -> UVarInt)
-> (UVarInt -> Int -> UVarInt)
-> UVarInt
-> (Int -> UVarInt)
-> (UVarInt -> Int -> UVarInt)
-> (UVarInt -> Int -> UVarInt)
-> (UVarInt -> Int -> UVarInt)
-> (UVarInt -> Int -> Bool)
-> (UVarInt -> Maybe Int)
-> (UVarInt -> Int)
-> (UVarInt -> Bool)
-> (UVarInt -> Int -> UVarInt)
-> (UVarInt -> Int -> UVarInt)
-> (UVarInt -> Int -> UVarInt)
-> (UVarInt -> Int -> UVarInt)
-> (UVarInt -> Int -> UVarInt)
-> (UVarInt -> Int -> UVarInt)
-> (UVarInt -> Int)
-> Bits UVarInt
Int -> UVarInt
UVarInt -> Bool
UVarInt -> Int
UVarInt -> Maybe Int
UVarInt -> UVarInt
UVarInt -> Int -> Bool
UVarInt -> Int -> UVarInt
UVarInt -> UVarInt -> UVarInt
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
$c.&. :: UVarInt -> UVarInt -> UVarInt
.&. :: UVarInt -> UVarInt -> UVarInt
$c.|. :: UVarInt -> UVarInt -> UVarInt
.|. :: UVarInt -> UVarInt -> UVarInt
$cxor :: UVarInt -> UVarInt -> UVarInt
xor :: UVarInt -> UVarInt -> UVarInt
$ccomplement :: UVarInt -> UVarInt
complement :: UVarInt -> UVarInt
$cshift :: UVarInt -> Int -> UVarInt
shift :: UVarInt -> Int -> UVarInt
$crotate :: UVarInt -> Int -> UVarInt
rotate :: UVarInt -> Int -> UVarInt
$czeroBits :: UVarInt
zeroBits :: UVarInt
$cbit :: Int -> UVarInt
bit :: Int -> UVarInt
$csetBit :: UVarInt -> Int -> UVarInt
setBit :: UVarInt -> Int -> UVarInt
$cclearBit :: UVarInt -> Int -> UVarInt
clearBit :: UVarInt -> Int -> UVarInt
$ccomplementBit :: UVarInt -> Int -> UVarInt
complementBit :: UVarInt -> Int -> UVarInt
$ctestBit :: UVarInt -> Int -> Bool
testBit :: UVarInt -> Int -> Bool
$cbitSizeMaybe :: UVarInt -> Maybe Int
bitSizeMaybe :: UVarInt -> Maybe Int
$cbitSize :: UVarInt -> Int
bitSize :: UVarInt -> Int
$cisSigned :: UVarInt -> Bool
isSigned :: UVarInt -> Bool
$cshiftL :: UVarInt -> Int -> UVarInt
shiftL :: UVarInt -> Int -> UVarInt
$cunsafeShiftL :: UVarInt -> Int -> UVarInt
unsafeShiftL :: UVarInt -> Int -> UVarInt
$cshiftR :: UVarInt -> Int -> UVarInt
shiftR :: UVarInt -> Int -> UVarInt
$cunsafeShiftR :: UVarInt -> Int -> UVarInt
unsafeShiftR :: UVarInt -> Int -> UVarInt
$crotateL :: UVarInt -> Int -> UVarInt
rotateL :: UVarInt -> Int -> UVarInt
$crotateR :: UVarInt -> Int -> UVarInt
rotateR :: UVarInt -> Int -> UVarInt
$cpopCount :: UVarInt -> Int
popCount :: UVarInt -> Int
Bits, Int -> UVarInt
UVarInt -> Int
UVarInt -> [UVarInt]
UVarInt -> UVarInt
UVarInt -> UVarInt -> [UVarInt]
UVarInt -> UVarInt -> UVarInt -> [UVarInt]
(UVarInt -> UVarInt)
-> (UVarInt -> UVarInt)
-> (Int -> UVarInt)
-> (UVarInt -> Int)
-> (UVarInt -> [UVarInt])
-> (UVarInt -> UVarInt -> [UVarInt])
-> (UVarInt -> UVarInt -> [UVarInt])
-> (UVarInt -> UVarInt -> UVarInt -> [UVarInt])
-> Enum UVarInt
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 :: UVarInt -> UVarInt
succ :: UVarInt -> UVarInt
$cpred :: UVarInt -> UVarInt
pred :: UVarInt -> UVarInt
$ctoEnum :: Int -> UVarInt
toEnum :: Int -> UVarInt
$cfromEnum :: UVarInt -> Int
fromEnum :: UVarInt -> Int
$cenumFrom :: UVarInt -> [UVarInt]
enumFrom :: UVarInt -> [UVarInt]
$cenumFromThen :: UVarInt -> UVarInt -> [UVarInt]
enumFromThen :: UVarInt -> UVarInt -> [UVarInt]
$cenumFromTo :: UVarInt -> UVarInt -> [UVarInt]
enumFromTo :: UVarInt -> UVarInt -> [UVarInt]
$cenumFromThenTo :: UVarInt -> UVarInt -> UVarInt -> [UVarInt]
enumFromThenTo :: UVarInt -> UVarInt -> UVarInt -> [UVarInt]
Enum, Eq UVarInt
Eq UVarInt =>
(UVarInt -> UVarInt -> Ordering)
-> (UVarInt -> UVarInt -> Bool)
-> (UVarInt -> UVarInt -> Bool)
-> (UVarInt -> UVarInt -> Bool)
-> (UVarInt -> UVarInt -> Bool)
-> (UVarInt -> UVarInt -> UVarInt)
-> (UVarInt -> UVarInt -> UVarInt)
-> Ord UVarInt
UVarInt -> UVarInt -> Bool
UVarInt -> UVarInt -> Ordering
UVarInt -> UVarInt -> UVarInt
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: UVarInt -> UVarInt -> Ordering
compare :: UVarInt -> UVarInt -> Ordering
$c< :: UVarInt -> UVarInt -> Bool
< :: UVarInt -> UVarInt -> Bool
$c<= :: UVarInt -> UVarInt -> Bool
<= :: UVarInt -> UVarInt -> Bool
$c> :: UVarInt -> UVarInt -> Bool
> :: UVarInt -> UVarInt -> Bool
$c>= :: UVarInt -> UVarInt -> Bool
>= :: UVarInt -> UVarInt -> Bool
$cmax :: UVarInt -> UVarInt -> UVarInt
max :: UVarInt -> UVarInt -> UVarInt
$cmin :: UVarInt -> UVarInt -> UVarInt
min :: UVarInt -> UVarInt -> UVarInt
Ord, Num UVarInt
Ord UVarInt
(Num UVarInt, Ord UVarInt) => (UVarInt -> Rational) -> Real UVarInt
UVarInt -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: UVarInt -> Rational
toRational :: UVarInt -> Rational
Real, Enum UVarInt
Real UVarInt
(Real UVarInt, Enum UVarInt) =>
(UVarInt -> UVarInt -> UVarInt)
-> (UVarInt -> UVarInt -> UVarInt)
-> (UVarInt -> UVarInt -> UVarInt)
-> (UVarInt -> UVarInt -> UVarInt)
-> (UVarInt -> UVarInt -> (UVarInt, UVarInt))
-> (UVarInt -> UVarInt -> (UVarInt, UVarInt))
-> (UVarInt -> Integer)
-> Integral UVarInt
UVarInt -> Integer
UVarInt -> UVarInt -> (UVarInt, UVarInt)
UVarInt -> UVarInt -> UVarInt
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: UVarInt -> UVarInt -> UVarInt
quot :: UVarInt -> UVarInt -> UVarInt
$crem :: UVarInt -> UVarInt -> UVarInt
rem :: UVarInt -> UVarInt -> UVarInt
$cdiv :: UVarInt -> UVarInt -> UVarInt
div :: UVarInt -> UVarInt -> UVarInt
$cmod :: UVarInt -> UVarInt -> UVarInt
mod :: UVarInt -> UVarInt -> UVarInt
$cquotRem :: UVarInt -> UVarInt -> (UVarInt, UVarInt)
quotRem :: UVarInt -> UVarInt -> (UVarInt, UVarInt)
$cdivMod :: UVarInt -> UVarInt -> (UVarInt, UVarInt)
divMod :: UVarInt -> UVarInt -> (UVarInt, UVarInt)
$ctoInteger :: UVarInt -> Integer
toInteger :: UVarInt -> Integer
Integral, UVarInt
UVarInt -> UVarInt -> Bounded UVarInt
forall a. a -> a -> Bounded a
$cminBound :: UVarInt
minBound :: UVarInt
$cmaxBound :: UVarInt
maxBound :: UVarInt
Bounded, UVarInt -> ()
(UVarInt -> ()) -> NFData UVarInt
forall a. (a -> ()) -> NFData a
$crnf :: UVarInt -> ()
rnf :: UVarInt -> ()
NFData)


major, minor, patch :: UVarInt
major :: UVarInt
major = case Version -> [Int]
versionBranch Version
version of (Int
x:[Int]
_) -> Int -> UVarInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x; [Int]
_ -> UVarInt
0
minor :: UVarInt
minor = case Version -> [Int]
versionBranch Version
version of (Int
_:Int
x:[Int]
_) -> Int -> UVarInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x; [Int]
_ -> UVarInt
0
patch :: UVarInt
patch = case Version -> [Int]
versionBranch Version
version of (Int
_:Int
_:Int
x:[Int]
_) -> Int -> UVarInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x; [Int]
_ -> UVarInt
0

clientName :: ChString
clientName :: ChString
clientName = String -> ChString
forall a. IsString a => String -> a
fromString (String -> ChString) -> String -> ChString
forall a b. (a -> b) -> a -> b
$
  String
"ClickHaskell-" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> UVarInt -> String
forall a. Show a => a -> String
show UVarInt
major String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"." String -> ShowS
forall a. Semigroup a => a -> a -> a
<> UVarInt -> String
forall a. Show a => a -> String
show UVarInt
minor String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"." String -> ShowS
forall a. Semigroup a => a -> a -> a
<> UVarInt -> String
forall a. Show a => a -> String
show UVarInt
patch

newtype ProtocolRevision = MkProtocolRevision UVarInt
  deriving newtype (ProtocolRevision -> ProtocolRevision -> Bool
(ProtocolRevision -> ProtocolRevision -> Bool)
-> (ProtocolRevision -> ProtocolRevision -> Bool)
-> Eq ProtocolRevision
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ProtocolRevision -> ProtocolRevision -> Bool
== :: ProtocolRevision -> ProtocolRevision -> Bool
$c/= :: ProtocolRevision -> ProtocolRevision -> Bool
/= :: ProtocolRevision -> ProtocolRevision -> Bool
Eq, Integer -> ProtocolRevision
ProtocolRevision -> ProtocolRevision
ProtocolRevision -> ProtocolRevision -> ProtocolRevision
(ProtocolRevision -> ProtocolRevision -> ProtocolRevision)
-> (ProtocolRevision -> ProtocolRevision -> ProtocolRevision)
-> (ProtocolRevision -> ProtocolRevision -> ProtocolRevision)
-> (ProtocolRevision -> ProtocolRevision)
-> (ProtocolRevision -> ProtocolRevision)
-> (ProtocolRevision -> ProtocolRevision)
-> (Integer -> ProtocolRevision)
-> Num ProtocolRevision
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: ProtocolRevision -> ProtocolRevision -> ProtocolRevision
+ :: ProtocolRevision -> ProtocolRevision -> ProtocolRevision
$c- :: ProtocolRevision -> ProtocolRevision -> ProtocolRevision
- :: ProtocolRevision -> ProtocolRevision -> ProtocolRevision
$c* :: ProtocolRevision -> ProtocolRevision -> ProtocolRevision
* :: ProtocolRevision -> ProtocolRevision -> ProtocolRevision
$cnegate :: ProtocolRevision -> ProtocolRevision
negate :: ProtocolRevision -> ProtocolRevision
$cabs :: ProtocolRevision -> ProtocolRevision
abs :: ProtocolRevision -> ProtocolRevision
$csignum :: ProtocolRevision -> ProtocolRevision
signum :: ProtocolRevision -> ProtocolRevision
$cfromInteger :: Integer -> ProtocolRevision
fromInteger :: Integer -> ProtocolRevision
Num, Eq ProtocolRevision
Eq ProtocolRevision =>
(ProtocolRevision -> ProtocolRevision -> Ordering)
-> (ProtocolRevision -> ProtocolRevision -> Bool)
-> (ProtocolRevision -> ProtocolRevision -> Bool)
-> (ProtocolRevision -> ProtocolRevision -> Bool)
-> (ProtocolRevision -> ProtocolRevision -> Bool)
-> (ProtocolRevision -> ProtocolRevision -> ProtocolRevision)
-> (ProtocolRevision -> ProtocolRevision -> ProtocolRevision)
-> Ord ProtocolRevision
ProtocolRevision -> ProtocolRevision -> Bool
ProtocolRevision -> ProtocolRevision -> Ordering
ProtocolRevision -> ProtocolRevision -> ProtocolRevision
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ProtocolRevision -> ProtocolRevision -> Ordering
compare :: ProtocolRevision -> ProtocolRevision -> Ordering
$c< :: ProtocolRevision -> ProtocolRevision -> Bool
< :: ProtocolRevision -> ProtocolRevision -> Bool
$c<= :: ProtocolRevision -> ProtocolRevision -> Bool
<= :: ProtocolRevision -> ProtocolRevision -> Bool
$c> :: ProtocolRevision -> ProtocolRevision -> Bool
> :: ProtocolRevision -> ProtocolRevision -> Bool
$c>= :: ProtocolRevision -> ProtocolRevision -> Bool
>= :: ProtocolRevision -> ProtocolRevision -> Bool
$cmax :: ProtocolRevision -> ProtocolRevision -> ProtocolRevision
max :: ProtocolRevision -> ProtocolRevision -> ProtocolRevision
$cmin :: ProtocolRevision -> ProtocolRevision -> ProtocolRevision
min :: ProtocolRevision -> ProtocolRevision -> ProtocolRevision
Ord, ProtocolRevision -> ProtocolRevision -> Builder
(ProtocolRevision -> ProtocolRevision -> Builder)
-> Serializable ProtocolRevision
forall chType.
(ProtocolRevision -> chType -> Builder) -> Serializable chType
$cserialize :: ProtocolRevision -> ProtocolRevision -> Builder
serialize :: ProtocolRevision -> ProtocolRevision -> Builder
Serializable)

{-# INLINE [0] afterRevision #-}
afterRevision
  :: forall rev monoid
  . (KnownNat rev, Monoid monoid)
  => ProtocolRevision -> monoid -> monoid
afterRevision :: forall (rev :: Nat) monoid.
(KnownNat rev, Monoid monoid) =>
ProtocolRevision -> monoid -> monoid
afterRevision ProtocolRevision
chosenRevision monoid
monoid =
  if ProtocolRevision
chosenRevision ProtocolRevision -> ProtocolRevision -> Bool
forall a. Ord a => a -> a -> Bool
>= (Integer -> ProtocolRevision
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> ProtocolRevision)
-> (Proxy rev -> Integer) -> Proxy rev -> ProtocolRevision
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy rev -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal) (forall (t :: Nat). Proxy t
forall {k} (t :: k). Proxy t
Proxy @rev)
  then monoid
monoid
  else monoid
forall a. Monoid a => a
mempty

latestSupportedRevision :: ProtocolRevision
latestSupportedRevision :: ProtocolRevision
latestSupportedRevision = (Integer -> ProtocolRevision
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> ProtocolRevision)
-> (Proxy DBMS_TCP_PROTOCOL_VERSION -> Integer)
-> Proxy DBMS_TCP_PROTOCOL_VERSION
-> ProtocolRevision
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy DBMS_TCP_PROTOCOL_VERSION -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal) (forall (t :: Nat). Proxy t
forall {k} (t :: k). Proxy t
Proxy @DBMS_TCP_PROTOCOL_VERSION)

data SinceRevision a (revisionNumber :: Nat) = MkSinceRevision a | NotPresented

instance
  (KnownNat revision, Deserializable chType)
  =>
  Deserializable (SinceRevision chType revision)
  where
  deserialize :: ProtocolRevision -> Get (SinceRevision chType revision)
deserialize ProtocolRevision
rev =
    if ProtocolRevision
rev ProtocolRevision -> ProtocolRevision -> Bool
forall a. Ord a => a -> a -> Bool
>= (Integer -> ProtocolRevision
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> ProtocolRevision)
-> (Proxy revision -> Integer)
-> Proxy revision
-> ProtocolRevision
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy revision -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal) (forall (t :: Nat). Proxy t
forall {k} (t :: k). Proxy t
Proxy @revision)
    then chType -> SinceRevision chType revision
forall a (revisionNumber :: Nat).
a -> SinceRevision a revisionNumber
MkSinceRevision (chType -> SinceRevision chType revision)
-> Get chType -> Get (SinceRevision chType revision)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall chType.
Deserializable chType =>
ProtocolRevision -> Get chType
deserialize @chType ProtocolRevision
rev
    else SinceRevision chType revision
-> Get (SinceRevision chType revision)
forall a. a -> Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure SinceRevision chType revision
forall a (revisionNumber :: Nat). SinceRevision a revisionNumber
NotPresented

instance
  (KnownNat revision, Serializable chType)
  =>
  Serializable (SinceRevision chType revision)
  where
  serialize :: ProtocolRevision -> SinceRevision chType revision -> Builder
serialize ProtocolRevision
rev (MkSinceRevision chType
val) = forall (rev :: Nat) monoid.
(KnownNat rev, Monoid monoid) =>
ProtocolRevision -> monoid -> monoid
afterRevision @revision ProtocolRevision
rev (ProtocolRevision -> chType -> Builder
forall chType.
Serializable chType =>
ProtocolRevision -> chType -> Builder
serialize ProtocolRevision
rev chType
val)
  serialize ProtocolRevision
rev SinceRevision chType revision
NotPresented          = forall (rev :: Nat) monoid.
(KnownNat rev, Monoid monoid) =>
ProtocolRevision -> monoid -> monoid
afterRevision @revision ProtocolRevision
rev (String -> Builder
forall a. HasCallStack => String -> a
error String
"Unexpected error")


{-
  Slightly modified C++ sources:
  https://github.com/ClickHouse/ClickHouse/blob/eb4a74d7412a1fcf52727cd8b00b365d6b9ed86c/src/Core/ProtocolDefines.h#L6
-}
type DBMS_TCP_PROTOCOL_VERSION = 54448;

type DBMS_MIN_REVISION_WITH_CLIENT_INFO = 54032;
type DBMS_MIN_REVISION_WITH_SERVER_TIMEZONE = 54058;
type DBMS_MIN_REVISION_WITH_QUOTA_KEY_IN_CLIENT_INFO = 54060;
type DBMS_MIN_REVISION_WITH_TABLES_STATUS = 54226;
type DBMS_MIN_REVISION_WITH_TIME_ZONE_PARAMETER_IN_DATETIME_DATA_TYPE = 54337;
type DBMS_MIN_REVISION_WITH_SERVER_DISPLAY_NAME = 54372;
type DBMS_MIN_REVISION_WITH_VERSION_PATCH = 54401;
type DBMS_MIN_REVISION_WITH_SERVER_LOGS = 54406;
type DBMS_MIN_REVISION_WITH_CURRENT_AGGREGATION_VARIANT_SELECTION_METHOD = 54448;
type DBMS_MIN_MAJOR_VERSION_WITH_CURRENT_AGGREGATION_VARIANT_SELECTION_METHOD = 21;
type DBMS_MIN_MINOR_VERSION_WITH_CURRENT_AGGREGATION_VARIANT_SELECTION_METHOD = 4;
type DBMS_MIN_REVISION_WITH_COLUMN_DEFAULTS_METADATA = 54410;
type DBMS_MIN_REVISION_WITH_LOW_CARDINALITY_TYPE = 54405;
type DBMS_MIN_REVISION_WITH_CLIENT_WRITE_INFO = 54420;
type DBMS_MIN_REVISION_WITH_SETTINGS_SERIALIZED_AS_STRINGS = 54429;
type DBMS_MIN_REVISION_WITH_SCALARS = 54429;
type DBMS_MIN_REVISION_WITH_OPENTELEMETRY = 54442;
type DBMS_MIN_REVISION_WITH_AGGREGATE_FUNCTIONS_VERSIONING = 54452;
type DBMS_CLUSTER_PROCESSING_PROTOCOL_VERSION = 1;
type DBMS_MIN_SUPPORTED_PARALLEL_REPLICAS_PROTOCOL_VERSION = 3;
type DBMS_PARALLEL_REPLICAS_MIN_VERSION_WITH_MARK_SEGMENT_SIZE_FIELD = 4;
type DBMS_PARALLEL_REPLICAS_PROTOCOL_VERSION = 4;
type DBMS_MIN_REVISION_WITH_PARALLEL_REPLICAS = 54453;
type DBMS_MERGE_TREE_PART_INFO_VERSION = 1;
type DBMS_MIN_REVISION_WITH_INTERSERVER_SECRET = 54441;
type DBMS_MIN_REVISION_WITH_X_FORWARDED_FOR_IN_CLIENT_INFO = 54443;
type DBMS_MIN_REVISION_WITH_REFERER_IN_CLIENT_INFO = 54447;
type DBMS_MIN_PROTOCOL_VERSION_WITH_DISTRIBUTED_DEPTH = 54448;
type DBMS_MIN_PROTOCOL_VERSION_WITH_INCREMENTAL_PROFILE_EVENTS = 54451;
type DBMS_MIN_REVISION_WITH_CUSTOM_SERIALIZATION = 54454;
type DBMS_MIN_PROTOCOL_VERSION_WITH_INITIAL_QUERY_START_TIME = 54449;
type DBMS_MIN_PROTOCOL_VERSION_WITH_PROFILE_EVENTS_IN_INSERT = 54456;
type DBMS_MIN_PROTOCOL_VERSION_WITH_VIEW_IF_PERMITTED = 54457;
type DBMS_MIN_PROTOCOL_VERSION_WITH_ADDENDUM = 54458;
type DBMS_MIN_PROTOCOL_VERSION_WITH_QUOTA_KEY = 54458;
type DBMS_MIN_PROTOCOL_VERSION_WITH_PARAMETERS = 54459;
type DBMS_MIN_PROTOCOL_VERSION_WITH_SERVER_QUERY_TIME_IN_PROGRESS = 54460;
type DBMS_MIN_PROTOCOL_VERSION_WITH_PASSWORD_COMPLEXITY_RULES = 54461;
type DBMS_MIN_REVISION_WITH_INTERSERVER_SECRET_V2 = 54462;
type DBMS_MIN_PROTOCOL_VERSION_WITH_TOTAL_BYTES_IN_PROGRESS = 54463;
type DBMS_MIN_PROTOCOL_VERSION_WITH_TIMEZONE_UPDATES = 54464;
type DBMS_MIN_REVISION_WITH_SPARSE_SERIALIZATION = 54465;
type DBMS_MIN_REVISION_WITH_SSH_AUTHENTICATION = 54466;
type DBMS_MIN_REVISION_WITH_TABLE_READ_ONLY_CHECK = 54467;
type DBMS_MIN_REVISION_WITH_SYSTEM_KEYWORDS_TABLE = 54468;
type DBMS_MIN_REVISION_WITH_ROWS_BEFORE_AGGREGATION = 54469;
type DBMS_MIN_PROTOCOL_VERSION_WITH_CHUNKED_PACKETS = 54470;
type DBMS_MIN_REVISION_WITH_VERSIONED_PARALLEL_REPLICAS_PROTOCOL = 54471;