Copyright | (c) 2023 Dmitry Kovalev |
---|---|
License | BSD-3-Clause |
Maintainer | Dmitry Kovalev |
Stability | Experimental |
Safe Haskell | None |
Language | Haskell2010 |
ClickHaskell
Description
For full documentation, visit: https://clickhaskell.dev/
Synopsis
- data ConnectionArgs
- defaultConnectionArgs :: ConnectionArgs
- setHost :: HostName -> ConnectionArgs -> ConnectionArgs
- setPort :: ServiceName -> ConnectionArgs -> ConnectionArgs
- setUser :: Text -> ConnectionArgs -> ConnectionArgs
- setDatabase :: Text -> ConnectionArgs -> ConnectionArgs
- setPassword :: Text -> ConnectionArgs -> ConnectionArgs
- data Connection where
- MkConnection :: MVar ConnectionState -> Connection
- openConnection :: HasCallStack => ConnectionArgs -> IO Connection
- setSecure :: ConnectionArgs -> ConnectionArgs
- overrideTLS :: ClientParams -> ConnectionArgs -> ConnectionArgs
- data ClientError where
- UserError :: HasCallStack => UserError -> ClientError
- InternalError :: HasCallStack => InternalError -> ClientError
- data ConnectionError
- data UserError
- data InternalError
- select :: forall (columns :: [Type]) output result. ClickHaskell columns output => Connection -> ChString -> ([output] -> IO result) -> IO [result]
- selectFrom :: ClickHaskellTable table output => Connection -> ([output] -> IO result) -> IO [result]
- selectFromView :: forall view output result (name :: Symbol) (columns :: [Type]) (parameters :: [Type]) (passedParameters :: [Type]). (ClickHaskell columns output, KnownSymbol name, view ~ View name columns parameters) => Connection -> (Parameters ('[] :: [Type]) -> Parameters passedParameters) -> ([output] -> IO result) -> IO [result]
- generateRandom :: forall (columns :: [Type]) output result. ClickHaskell columns output => Connection -> (UInt64, UInt64, UInt64) -> UInt64 -> ([output] -> IO result) -> IO [result]
- class ClickHaskell (columns :: [Type]) record where
- deserializeColumns :: Bool -> ProtocolRevision -> UVarInt -> Get [record]
- columns :: Builder
- readingColumnsAndTypes :: Builder
- serializeRecords :: [record] -> ProtocolRevision -> Builder
- columnsCount :: UVarInt
- class FromChType chType outputType where
- fromChType :: chType -> outputType
- insertInto :: forall table record (name :: Symbol) (columns :: [Type]). (table ~ Table name columns, ClickHaskell columns record, KnownSymbol name) => Connection -> [record] -> IO ()
- class ToChType chType inputType where
- toChType :: inputType -> chType
- command :: HasCallStack => Connection -> ChString -> IO ()
- ping :: HasCallStack => Connection -> IO ()
- data Column (name :: Symbol) chType
- class (IsChType (GetColumnType column), KnownSymbol (GetColumnName column)) => KnownColumn column
- class SerializableColumn column
- data Table (name :: Symbol) (columns :: [Type])
- data View (name :: Symbol) (columns :: [Type]) (parameters :: [Type])
- class ToQueryPart chType where
- toQueryPart :: chType -> Builder
- parameter :: forall (name :: Symbol) chType (parameters :: [Type]) userType. (ToChType chType userType, KnownParameter (Parameter name chType)) => userType -> Parameters parameters -> Parameters (Parameter name chType ': parameters)
- data Parameter (name :: Symbol) chType
- data Parameters (parameters :: [Type])
- viewParameters :: forall (passedParameters :: [Type]). (Parameters ('[] :: [Type]) -> Parameters passedParameters) -> Builder
- class IsChType chType where
- chTypeName :: String
- defaultValueOfTypeName :: chType
- newtype DateTime (tz :: Symbol) = MkDateTime Word32
- data DateTime64 (precision :: Nat) (tz :: Symbol)
- data Int8
- data Int16
- data Int32
- data Int64
- data Int128 = Int128 {
- int128Hi64 :: !Word64
- int128Lo64 :: !Word64
- type UInt8 = Word8
- type UInt16 = Word16
- type UInt32 = Word32
- type UInt64 = Word64
- type UInt128 = Word128
- data Word128 = Word128 {
- word128Hi64 :: !Word64
- word128Lo64 :: !Word64
- type Nullable = Maybe
- data LowCardinality chType
- class IsChType chType => IsLowCardinalitySupported chType
- newtype UUID = MkChUUID Word128
- newtype Array a = MkChArray [a]
- newtype ChString = MkChString ByteString
- newtype UVarInt = MkUVarInt Word64
- data SinceRevision a (revisionNumber :: Nat)
- data ProtocolRevision
- data DataPacket = MkDataPacket {}
- data BlockInfo = MkBlockInfo {
- field_num1 :: UVarInt
- is_overflows :: UInt8
- field_num2 :: UVarInt
- bucket_num :: Int32
- eof :: UVarInt
- data ClientPacket where
- Hello :: HelloPacket -> ClientPacket
- Query :: QueryPacket -> ClientPacket
- Data :: DataPacket -> ClientPacket
- Cancel :: ClientPacket
- Ping :: ClientPacket
- TablesStatusRequest :: ClientPacket
- KeepAlive :: ClientPacket
- Scalar :: ClientPacket
- IgnoredPartUUIDs :: ClientPacket
- ReadTaskResponse :: ClientPacket
- MergeTreeReadTaskResponse :: ClientPacket
- SSHChallengeRequest :: ClientPacket
- SSHChallengeResponse :: ClientPacket
- data HelloPacket = MkHelloPacket {}
- data Addendum = MkAddendum {
- quota_key :: SinceRevision ChString DBMS_MIN_PROTOCOL_VERSION_WITH_QUOTA_KEY
- data QueryPacket = MkQueryPacket {
- query_id :: ChString
- client_info :: SinceRevision ClientInfo DBMS_MIN_REVISION_WITH_CLIENT_INFO
- settings :: DbSettings
- interserver_secret :: SinceRevision ChString DBMS_MIN_REVISION_WITH_INTERSERVER_SECRET
- query_stage :: QueryStage
- compression :: UVarInt
- query :: ChString
- parameters :: SinceRevision QueryParameters DBMS_MIN_PROTOCOL_VERSION_WITH_PARAMETERS
- data DbSettings = MkDbSettings
- data QueryParameters = MkQueryParameters
- data QueryStage
- data ClientInfo = MkClientInfo {
- query_kind :: QueryKind
- initial_user :: ChString
- initial_query_id :: ChString
- initial_adress :: ChString
- initial_time :: SinceRevision Int64 DBMS_MIN_PROTOCOL_VERSION_WITH_INITIAL_QUERY_START_TIME
- interface_type :: UInt8
- os_user :: ChString
- hostname :: ChString
- client_name :: ChString
- client_version_major :: UVarInt
- client_version_minor :: UVarInt
- client_revision :: ProtocolRevision
- quota_key :: SinceRevision ChString DBMS_MIN_REVISION_WITH_QUOTA_KEY_IN_CLIENT_INFO
- distrubuted_depth :: SinceRevision UVarInt DBMS_MIN_PROTOCOL_VERSION_WITH_DISTRIBUTED_DEPTH
- client_version_patch :: SinceRevision UVarInt DBMS_MIN_REVISION_WITH_VERSION_PATCH
- open_telemetry :: SinceRevision UInt8 DBMS_MIN_REVISION_WITH_OPENTELEMETRY
- collaborate_with_initiator :: SinceRevision UVarInt DBMS_MIN_REVISION_WITH_PARALLEL_REPLICAS
- count_participating_replicas :: SinceRevision UVarInt DBMS_MIN_REVISION_WITH_PARALLEL_REPLICAS
- number_of_current_replica :: SinceRevision UVarInt DBMS_MIN_REVISION_WITH_PARALLEL_REPLICAS
- data QueryKind
- data ServerPacket where
- HelloResponse :: HelloResponse -> ServerPacket
- DataResponse :: DataPacket -> ServerPacket
- Exception :: ExceptionPacket -> ServerPacket
- Progress :: ProgressPacket -> ServerPacket
- Pong :: ServerPacket
- EndOfStream :: ServerPacket
- ProfileInfo :: ProfileInfo -> ServerPacket
- Totals :: ServerPacket
- Extremes :: ServerPacket
- TablesStatusResponse :: ServerPacket
- Log :: ServerPacket
- TableColumns :: TableColumns -> ServerPacket
- UUIDs :: ServerPacket
- ReadTaskRequest :: ServerPacket
- ProfileEvents :: ServerPacket
- UnknownPacket :: UVarInt -> ServerPacket
- data HelloResponse = MkHelloResponse {
- server_name :: ChString
- server_version_major :: UVarInt
- server_version_minor :: UVarInt
- server_revision :: ProtocolRevision
- server_parallel_replicas_proto :: SinceRevision UVarInt DBMS_MIN_REVISION_WITH_VERSIONED_PARALLEL_REPLICAS_PROTOCOL
- server_timezone :: SinceRevision ChString DBMS_MIN_REVISION_WITH_SERVER_TIMEZONE
- server_display_name :: SinceRevision ChString DBMS_MIN_REVISION_WITH_SERVER_DISPLAY_NAME
- server_version_patch :: SinceRevision UVarInt DBMS_MIN_REVISION_WITH_VERSION_PATCH
- proto_send_chunked_srv :: SinceRevision ChString DBMS_MIN_PROTOCOL_VERSION_WITH_CHUNKED_PACKETS
- proto_recv_chunked_srv :: SinceRevision ChString DBMS_MIN_PROTOCOL_VERSION_WITH_CHUNKED_PACKETS
- password_complexity_rules :: SinceRevision [PasswordComplexityRules] DBMS_MIN_PROTOCOL_VERSION_WITH_PASSWORD_COMPLEXITY_RULES
- read_nonce :: SinceRevision UInt64 DBMS_MIN_REVISION_WITH_INTERSERVER_SECRET_V2
- data PasswordComplexityRules = MkPasswordComplexityRules {}
- data ExceptionPacket = MkExceptionPacket {}
- data ProgressPacket = MkProgressPacket {
- rows :: UVarInt
- bytes :: UVarInt
- total_rows :: UVarInt
- total_bytes :: SinceRevision UVarInt DBMS_MIN_PROTOCOL_VERSION_WITH_TOTAL_BYTES_IN_PROGRESS
- wrote_rows :: SinceRevision UVarInt DBMS_MIN_PROTOCOL_VERSION_WITH_TOTAL_BYTES_IN_PROGRESS
- wrote_bytes :: SinceRevision UVarInt DBMS_MIN_REVISION_WITH_CLIENT_WRITE_INFO
- elapsed_ns :: SinceRevision UVarInt DBMS_MIN_REVISION_WITH_CLIENT_WRITE_INFO
- data ProfileInfo = MkProfileInfo {
- rows :: UVarInt
- blocks :: UVarInt
- bytes :: UVarInt
- applied_limit :: UInt8
- rows_before_limit :: UVarInt
- calculated_rows_before_limit :: UInt8
- applied_aggregation :: SinceRevision UInt8 DBMS_MIN_REVISION_WITH_ROWS_BEFORE_AGGREGATION
- rows_before_aggregation :: SinceRevision UVarInt DBMS_MIN_REVISION_WITH_ROWS_BEFORE_AGGREGATION
- data TableColumns = MkTableColumns {}
Connection
data ConnectionArgs Source #
See defaultConnectionArgs
for documentation
defaultConnectionArgs :: ConnectionArgs Source #
Default connection settings which follows clickhouse-client defaults
Use setUser
setPassword
setHost
setPort
setDatabase
to modify connection defaults.
Or setSecure
overrideTLS
to configure TLS connection
setHost :: HostName -> ConnectionArgs -> ConnectionArgs Source #
Overrides default hostname "localhost"
setPort :: ServiceName -> ConnectionArgs -> ConnectionArgs Source #
Overrides default port 9000 (or 9443 for TLS)
setUser :: Text -> ConnectionArgs -> ConnectionArgs Source #
Overrides default user "default"
setDatabase :: Text -> ConnectionArgs -> ConnectionArgs Source #
Overrides default database "default"
setPassword :: Text -> ConnectionArgs -> ConnectionArgs Source #
Overrides default password ""
data Connection where Source #
Constructors
MkConnection :: MVar ConnectionState -> Connection |
openConnection :: HasCallStack => ConnectionArgs -> IO Connection Source #
TLS
setSecure :: ConnectionArgs -> ConnectionArgs Source #
Sets TLS connection
Uses 9443 port by default. Watch setPort
to override it
overrideTLS :: ClientParams -> ConnectionArgs -> ConnectionArgs Source #
Sets custom TLS settings and applies setSecure
Errors
data ClientError where Source #
A wrapper for all client-related errors. Every client function should handle this error.
Constructors
UserError :: HasCallStack => UserError -> ClientError | |
InternalError :: HasCallStack => InternalError -> ClientError |
Instances
Exception ClientError Source # | |
Defined in ClickHaskell Methods toException :: ClientError -> SomeException # fromException :: SomeException -> Maybe ClientError # displayException :: ClientError -> String # | |
Show ClientError Source # | |
Defined in ClickHaskell Methods showsPrec :: Int -> ClientError -> ShowS # show :: ClientError -> String # showList :: [ClientError] -> ShowS # |
data ConnectionError Source #
Errors occured on connection operations
Constructors
NoAdressResolved | Occurs when |
EstablishTimeout | Occurs on |
Instances
Exception ConnectionError Source # | |
Defined in ClickHaskell Methods toException :: ConnectionError -> SomeException # | |
Show ConnectionError Source # | |
Defined in ClickHaskell Methods showsPrec :: Int -> ConnectionError -> ShowS # show :: ConnectionError -> String # showList :: [ConnectionError] -> ShowS # |
Errors intended to be handled by developers
Constructors
UnmatchedType String | Column type mismatch in data packet |
UnmatchedColumn String | Column name mismatch in data packet |
UnmatchedColumnsCount String | Occurs when actual columns count less or more than expected |
DatabaseException ExceptionPacket | Database responded with an exception packet |
Instances
Exception UserError Source # | |
Defined in ClickHaskell Methods toException :: UserError -> SomeException # fromException :: SomeException -> Maybe UserError # displayException :: UserError -> String # | |
Show UserError Source # | |
data InternalError Source #
These exceptions might indicate internal bugs. If you encounter one, please report it.
Constructors
UnexpectedPacketType UVarInt | |
DeserializationError String |
Instances
Exception InternalError Source # | |
Defined in ClickHaskell Methods toException :: InternalError -> SomeException # fromException :: SomeException -> Maybe InternalError # displayException :: InternalError -> String # | |
Show InternalError Source # | |
Defined in ClickHaskell Methods showsPrec :: Int -> InternalError -> ShowS # show :: InternalError -> String # showList :: [InternalError] -> ShowS # |
Client wrappers
SELECT
select :: forall (columns :: [Type]) output result. ClickHaskell columns output => Connection -> ChString -> ([output] -> IO result) -> IO [result] Source #
selectFrom :: ClickHaskellTable table output => Connection -> ([output] -> IO result) -> IO [result] Source #
selectFromView :: forall view output result (name :: Symbol) (columns :: [Type]) (parameters :: [Type]) (passedParameters :: [Type]). (ClickHaskell columns output, KnownSymbol name, view ~ View name columns parameters) => Connection -> (Parameters ('[] :: [Type]) -> Parameters passedParameters) -> ([output] -> IO result) -> IO [result] Source #
generateRandom :: forall (columns :: [Type]) output result. ClickHaskell columns output => Connection -> (UInt64, UInt64, UInt64) -> UInt64 -> ([output] -> IO result) -> IO [result] Source #
class ClickHaskell (columns :: [Type]) record where Source #
Minimal complete definition
Nothing
Methods
deserializeColumns :: Bool -> ProtocolRevision -> UVarInt -> Get [record] Source #
default deserializeColumns :: GenericClickHaskell record columns => Bool -> ProtocolRevision -> UVarInt -> Get [record] Source #
readingColumnsAndTypes :: Builder Source #
default readingColumnsAndTypes :: GenericClickHaskell record columns => Builder Source #
serializeRecords :: [record] -> ProtocolRevision -> Builder Source #
default serializeRecords :: GenericClickHaskell record columns => [record] -> ProtocolRevision -> Builder Source #
columnsCount :: UVarInt Source #
default columnsCount :: GenericClickHaskell record columns => UVarInt Source #
class FromChType chType outputType where Source #
Methods
fromChType :: chType -> outputType Source #
Instances
FromChType ChString Builder Source # | |
Defined in ClickHaskell Methods fromChType :: ChString -> Builder Source # | |
FromChType ChString ByteString Source # | |
Defined in ClickHaskell Methods fromChType :: ChString -> ByteString Source # | |
(TypeError ('Text "ChString to Text using FromChType convertion could cause exception" ':$$: 'Text "Decode ByteString manually if you are sure it's always can be decoded or replace it with ByteString") :: Constraint) => FromChType ChString Text Source # | |
Defined in ClickHaskell Methods fromChType :: ChString -> Text Source # | |
(IsChType chType, chType ~ inputType) => FromChType chType inputType Source # | |
Defined in ClickHaskell Methods fromChType :: chType -> inputType Source # | |
FromChType chType (LowCardinality chType) Source # | |
Defined in ClickHaskell Methods fromChType :: chType -> LowCardinality chType Source # | |
FromChType UUID (Word64, Word64) Source # | |
Defined in ClickHaskell | |
FromChType (DateTime tz) Word32 Source # | |
Defined in ClickHaskell Methods fromChType :: DateTime tz -> Word32 Source # | |
FromChType (DateTime tz) UTCTime Source # | |
Defined in ClickHaskell Methods fromChType :: DateTime tz -> UTCTime Source # | |
FromChType chType outputType => FromChType (LowCardinality chType) outputType Source # | |
Defined in ClickHaskell Methods fromChType :: LowCardinality chType -> outputType Source # | |
FromChType chType inputType => FromChType (Array chType) [inputType] Source # | |
Defined in ClickHaskell Methods fromChType :: Array chType -> [inputType] Source # | |
FromChType chType inputType => FromChType (Nullable chType) (Nullable inputType) Source # | |
Defined in ClickHaskell Methods fromChType :: Nullable chType -> Nullable inputType Source # | |
FromChType (DateTime64 precision tz) Word64 Source # | |
Defined in ClickHaskell Methods fromChType :: DateTime64 precision tz -> Word64 Source # |
INSERT
insertInto :: forall table record (name :: Symbol) (columns :: [Type]). (table ~ Table name columns, ClickHaskell columns record, KnownSymbol name) => Connection -> [record] -> IO () Source #
class ToChType chType inputType where Source #
Instances
Arbitrary commands
command :: HasCallStack => Connection -> ChString -> IO () Source #
Might be used for any command without data responses
For example: CREATE, TRUNCATE, KILL, SET, GRANT
Throws exception if any data was returned
ping :: HasCallStack => Connection -> IO () Source #
Shared
data Column (name :: Symbol) chType Source #
Column declaration
For example:
type MyColumn = Column "myColumn" ChString
Instances
class (IsChType (GetColumnType column), KnownSymbol (GetColumnName column)) => KnownColumn column Source #
Minimal complete definition
mkColumn
Instances
class SerializableColumn column Source #
Minimal complete definition
deserializeColumn, serializeColumn
Instances
Query
class ToQueryPart chType where Source #
Methods
toQueryPart :: chType -> Builder Source #
Instances
parameter :: forall (name :: Symbol) chType (parameters :: [Type]) userType. (ToChType chType userType, KnownParameter (Parameter name chType)) => userType -> Parameters parameters -> Parameters (Parameter name chType ': parameters) Source #
data Parameters (parameters :: [Type]) Source #
viewParameters :: forall (passedParameters :: [Type]). (Parameters ('[] :: [Type]) -> Parameters passedParameters) -> Builder Source #
>>>
viewParameters (parameter @"a3" @ChString ("a3Val" :: String) . parameter @"a2" @ChString ("a2Val" :: String))
"(a3='a3Val', a2='a2Val')"
ClickHouse types
class IsChType chType where Source #
Methods
chTypeName :: String Source #
Shows database original type name
chTypeName @ChString = "String" chTypeName @(Nullable UInt32) = "Nullable(UInt32)"
defaultValueOfTypeName :: chType Source #
Instances
newtype DateTime (tz :: Symbol) Source #
ClickHouse DateTime column type (paramtrized with timezone)
>>>
chTypeName @(DateTime "")
"DateTime">>>
chTypeName @(DateTime "UTC")
"DateTime('UTC')"
Constructors
MkDateTime Word32 |
Instances
data DateTime64 (precision :: Nat) (tz :: Symbol) Source #
ClickHouse DateTime64 column type (paramtrized with timezone)
>>>
chTypeName @(DateTime64 3 "")
"DateTime64(3)">>>
chTypeName @(DateTime64 3 "UTC")
"DateTime64(3, 'UTC')"
Instances
(KnownSymbol tz, KnownNat precision) => IsChType (DateTime64 precision tz) Source # | |
Defined in ClickHaskell | |
(KnownSymbol name, IsChType (DateTime64 precision tz)) => KnownColumn (Column name (DateTime64 precision tz)) Source # | |
Defined in ClickHaskell Methods mkColumn :: [GetColumnType (Column name (DateTime64 precision tz))] -> Column (GetColumnName (Column name (DateTime64 precision tz))) (GetColumnType (Column name (DateTime64 precision tz))) | |
Bits (DateTime64 precision tz) Source # | |
Defined in ClickHaskell Methods (.&.) :: DateTime64 precision tz -> DateTime64 precision tz -> DateTime64 precision tz # (.|.) :: DateTime64 precision tz -> DateTime64 precision tz -> DateTime64 precision tz # xor :: DateTime64 precision tz -> DateTime64 precision tz -> DateTime64 precision tz # complement :: DateTime64 precision tz -> DateTime64 precision tz # shift :: DateTime64 precision tz -> Int -> DateTime64 precision tz # rotate :: DateTime64 precision tz -> Int -> DateTime64 precision tz # zeroBits :: DateTime64 precision tz # bit :: Int -> DateTime64 precision tz # setBit :: DateTime64 precision tz -> Int -> DateTime64 precision tz # clearBit :: DateTime64 precision tz -> Int -> DateTime64 precision tz # complementBit :: DateTime64 precision tz -> Int -> DateTime64 precision tz # testBit :: DateTime64 precision tz -> Int -> Bool # bitSizeMaybe :: DateTime64 precision tz -> Maybe Int # bitSize :: DateTime64 precision tz -> Int # isSigned :: DateTime64 precision tz -> Bool # shiftL :: DateTime64 precision tz -> Int -> DateTime64 precision tz # unsafeShiftL :: DateTime64 precision tz -> Int -> DateTime64 precision tz # shiftR :: DateTime64 precision tz -> Int -> DateTime64 precision tz # unsafeShiftR :: DateTime64 precision tz -> Int -> DateTime64 precision tz # rotateL :: DateTime64 precision tz -> Int -> DateTime64 precision tz # rotateR :: DateTime64 precision tz -> Int -> DateTime64 precision tz # popCount :: DateTime64 precision tz -> Int # | |
Bounded (DateTime64 precision tz) Source # | |
Defined in ClickHaskell | |
Enum (DateTime64 precision tz) Source # | |
Defined in ClickHaskell Methods succ :: DateTime64 precision tz -> DateTime64 precision tz # pred :: DateTime64 precision tz -> DateTime64 precision tz # toEnum :: Int -> DateTime64 precision tz # fromEnum :: DateTime64 precision tz -> Int # enumFrom :: DateTime64 precision tz -> [DateTime64 precision tz] # enumFromThen :: DateTime64 precision tz -> DateTime64 precision tz -> [DateTime64 precision tz] # enumFromTo :: DateTime64 precision tz -> DateTime64 precision tz -> [DateTime64 precision tz] # enumFromThenTo :: DateTime64 precision tz -> DateTime64 precision tz -> DateTime64 precision tz -> [DateTime64 precision tz] # | |
Num (DateTime64 precision tz) Source # | |
Defined in ClickHaskell Methods (+) :: 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 # negate :: DateTime64 precision tz -> DateTime64 precision tz # abs :: DateTime64 precision tz -> DateTime64 precision tz # signum :: DateTime64 precision tz -> DateTime64 precision tz # fromInteger :: Integer -> DateTime64 precision tz # | |
Integral (DateTime64 precision tz) Source # | |
Defined in ClickHaskell Methods quot :: DateTime64 precision tz -> DateTime64 precision tz -> DateTime64 precision tz # rem :: DateTime64 precision tz -> DateTime64 precision tz -> DateTime64 precision tz # div :: DateTime64 precision tz -> DateTime64 precision tz -> DateTime64 precision tz # mod :: DateTime64 precision tz -> DateTime64 precision tz -> DateTime64 precision tz # quotRem :: 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) # toInteger :: DateTime64 precision tz -> Integer # | |
Real (DateTime64 precision tz) Source # | |
Defined in ClickHaskell Methods toRational :: DateTime64 precision tz -> Rational # | |
Show (DateTime64 precision tz) Source # | |
Defined in ClickHaskell Methods showsPrec :: Int -> DateTime64 precision tz -> ShowS # show :: DateTime64 precision tz -> String # showList :: [DateTime64 precision tz] -> ShowS # | |
NFData (DateTime64 precision tz) Source # | |
Defined in ClickHaskell Methods rnf :: DateTime64 precision tz -> () # | |
Eq (DateTime64 precision tz) Source # | |
Defined in ClickHaskell Methods (==) :: DateTime64 precision tz -> DateTime64 precision tz -> Bool # (/=) :: DateTime64 precision tz -> DateTime64 precision tz -> Bool # | |
Ord (DateTime64 precision tz) Source # | |
Defined in ClickHaskell Methods compare :: 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 # max :: DateTime64 precision tz -> DateTime64 precision tz -> DateTime64 precision tz # min :: DateTime64 precision tz -> DateTime64 precision tz -> DateTime64 precision tz # | |
FromChType (DateTime64 precision tz) Word64 Source # | |
Defined in ClickHaskell Methods fromChType :: DateTime64 precision tz -> Word64 Source # | |
ToChType (DateTime64 precision tz) Word64 Source # | |
Defined in ClickHaskell Methods toChType :: Word64 -> DateTime64 precision tz Source # |
8-bit signed integer type
Instances
IsChType Int8 Source # | |||||
Defined in ClickHaskell | |||||
ToQueryPart Int8 Source # | |||||
Defined in ClickHaskell Methods toQueryPart :: Int8 -> Builder Source # | |||||
Data Int8 | Since: base-4.0.0.0 | ||||
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int8 -> c Int8 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int8 # dataTypeOf :: Int8 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Int8) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int8) # gmapT :: (forall b. Data b => b -> b) -> Int8 -> Int8 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int8 -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int8 -> r # gmapQ :: (forall d. Data d => d -> u) -> Int8 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Int8 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int8 -> m Int8 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int8 -> m Int8 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int8 -> m Int8 # | |||||
Storable Int8 | Since: base-2.1 | ||||
Defined in Foreign.Storable | |||||
Bits Int8 | Since: base-2.1 | ||||
Defined in GHC.Int Methods (.&.) :: Int8 -> Int8 -> Int8 # (.|.) :: Int8 -> Int8 -> Int8 # complement :: Int8 -> Int8 # shift :: Int8 -> Int -> Int8 # rotate :: Int8 -> Int -> Int8 # setBit :: Int8 -> Int -> Int8 # clearBit :: Int8 -> Int -> Int8 # complementBit :: Int8 -> Int -> Int8 # testBit :: Int8 -> Int -> Bool # bitSizeMaybe :: Int8 -> Maybe Int # shiftL :: Int8 -> Int -> Int8 # unsafeShiftL :: Int8 -> Int -> Int8 # shiftR :: Int8 -> Int -> Int8 # unsafeShiftR :: Int8 -> Int -> Int8 # rotateL :: Int8 -> Int -> Int8 # | |||||
FiniteBits Int8 | Since: base-4.6.0.0 | ||||
Defined in GHC.Int Methods finiteBitSize :: Int8 -> Int # countLeadingZeros :: Int8 -> Int # countTrailingZeros :: Int8 -> Int # | |||||
Bounded Int8 | Since: base-2.1 | ||||
Enum Int8 | Since: base-2.1 | ||||
Ix Int8 | Since: base-2.1 | ||||
Num Int8 | Since: base-2.1 | ||||
Read Int8 | Since: base-2.1 | ||||
Integral Int8 | Since: base-2.1 | ||||
Real Int8 | Since: base-2.1 | ||||
Defined in GHC.Int Methods toRational :: Int8 -> Rational # | |||||
Show Int8 | Since: base-2.1 | ||||
PrintfArg Int8 | Since: base-2.1 | ||||
Defined in Text.Printf | |||||
BitOps Int8 | |||||
FiniteBitsOps Int8 | |||||
Subtractive Int8 | |||||
Defined in Basement.Numerical.Subtractive Associated Types
| |||||
PrimMemoryComparable Int8 | |||||
Defined in Basement.PrimType | |||||
PrimType Int8 | |||||
Defined in Basement.PrimType Associated Types
Methods primSizeInBytes :: Proxy Int8 -> CountOf Word8 # primShiftToBytes :: Proxy Int8 -> Int # primBaUIndex :: ByteArray# -> Offset Int8 -> Int8 # primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset Int8 -> prim Int8 # primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset Int8 -> Int8 -> prim () # primAddrIndex :: Addr# -> Offset Int8 -> Int8 # primAddrRead :: PrimMonad prim => Addr# -> Offset Int8 -> prim Int8 # primAddrWrite :: PrimMonad prim => Addr# -> Offset Int8 -> Int8 -> prim () # | |||||
NFData Int8 | |||||
Defined in Control.DeepSeq | |||||
Eq Int8 | Since: base-2.1 | ||||
Ord Int8 | Since: base-2.1 | ||||
Hashable Int8 | |||||
Defined in Data.Hashable.Class | |||||
Unbox Int8 | |||||
Defined in Data.Vector.Unboxed.Base | |||||
Lift Int8 | |||||
Vector Vector Int8 | |||||
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s Int8 -> ST s (Vector Int8) basicUnsafeThaw :: Vector Int8 -> ST s (Mutable Vector s Int8) basicLength :: Vector Int8 -> Int basicUnsafeSlice :: Int -> Int -> Vector Int8 -> Vector Int8 basicUnsafeIndexM :: Vector Int8 -> Int -> Box Int8 basicUnsafeCopy :: Mutable Vector s Int8 -> Vector Int8 -> ST s () | |||||
MVector MVector Int8 | |||||
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s Int8 -> Int basicUnsafeSlice :: Int -> Int -> MVector s Int8 -> MVector s Int8 basicOverlaps :: MVector s Int8 -> MVector s Int8 -> Bool basicUnsafeNew :: Int -> ST s (MVector s Int8) basicInitialize :: MVector s Int8 -> ST s () basicUnsafeReplicate :: Int -> Int8 -> ST s (MVector s Int8) basicUnsafeRead :: MVector s Int8 -> Int -> ST s Int8 basicUnsafeWrite :: MVector s Int8 -> Int -> Int8 -> ST s () basicClear :: MVector s Int8 -> ST s () basicSet :: MVector s Int8 -> Int8 -> ST s () basicUnsafeCopy :: MVector s Int8 -> MVector s Int8 -> ST s () basicUnsafeMove :: MVector s Int8 -> MVector s Int8 -> ST s () basicUnsafeGrow :: MVector s Int8 -> Int -> ST s (MVector s Int8) | |||||
KnownSymbol name => KnownColumn (Column name Int8) Source # | |||||
Defined in ClickHaskell | |||||
type NatNumMaxBound Int8 | |||||
Defined in Basement.Nat | |||||
type Difference Int8 | |||||
Defined in Basement.Numerical.Subtractive | |||||
type PrimSize Int8 | |||||
Defined in Basement.PrimType | |||||
newtype Vector Int8 | |||||
Defined in Data.Vector.Unboxed.Base | |||||
newtype MVector s Int8 | |||||
Defined in Data.Vector.Unboxed.Base |
16-bit signed integer type
Instances
32-bit signed integer type
Instances
IsChType Int32 Source # | |||||
Defined in ClickHaskell | |||||
ToQueryPart Int32 Source # | |||||
Defined in ClickHaskell Methods toQueryPart :: Int32 -> Builder Source # | |||||
Data Int32 | Since: base-4.0.0.0 | ||||
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int32 -> c Int32 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int32 # dataTypeOf :: Int32 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Int32) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int32) # gmapT :: (forall b. Data b => b -> b) -> Int32 -> Int32 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int32 -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int32 -> r # gmapQ :: (forall d. Data d => d -> u) -> Int32 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Int32 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int32 -> m Int32 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int32 -> m Int32 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int32 -> m Int32 # | |||||
Storable Int32 | Since: base-2.1 | ||||
Bits Int32 | Since: base-2.1 | ||||
Defined in GHC.Int Methods (.&.) :: Int32 -> Int32 -> Int32 # (.|.) :: Int32 -> Int32 -> Int32 # xor :: Int32 -> Int32 -> Int32 # complement :: Int32 -> Int32 # shift :: Int32 -> Int -> Int32 # rotate :: Int32 -> Int -> Int32 # setBit :: Int32 -> Int -> Int32 # clearBit :: Int32 -> Int -> Int32 # complementBit :: Int32 -> Int -> Int32 # testBit :: Int32 -> Int -> Bool # bitSizeMaybe :: Int32 -> Maybe Int # shiftL :: Int32 -> Int -> Int32 # unsafeShiftL :: Int32 -> Int -> Int32 # shiftR :: Int32 -> Int -> Int32 # unsafeShiftR :: Int32 -> Int -> Int32 # rotateL :: Int32 -> Int -> Int32 # | |||||
FiniteBits Int32 | Since: base-4.6.0.0 | ||||
Defined in GHC.Int Methods finiteBitSize :: Int32 -> Int # countLeadingZeros :: Int32 -> Int # countTrailingZeros :: Int32 -> Int # | |||||
Bounded Int32 | Since: base-2.1 | ||||
Enum Int32 | Since: base-2.1 | ||||
Ix Int32 | Since: base-2.1 | ||||
Num Int32 | Since: base-2.1 | ||||
Read Int32 | Since: base-2.1 | ||||
Integral Int32 | Since: base-2.1 | ||||
Real Int32 | Since: base-2.1 | ||||
Defined in GHC.Int Methods toRational :: Int32 -> Rational # | |||||
Show Int32 | Since: base-2.1 | ||||
PrintfArg Int32 | Since: base-2.1 | ||||
Defined in Text.Printf | |||||
BitOps Int32 | |||||
Defined in Basement.Bits | |||||
FiniteBitsOps Int32 | |||||
Defined in Basement.Bits | |||||
Subtractive Int32 | |||||
Defined in Basement.Numerical.Subtractive Associated Types
| |||||
PrimMemoryComparable Int32 | |||||
Defined in Basement.PrimType | |||||
PrimType Int32 | |||||
Defined in Basement.PrimType Associated Types
Methods primSizeInBytes :: Proxy Int32 -> CountOf Word8 # primShiftToBytes :: Proxy Int32 -> Int # primBaUIndex :: ByteArray# -> Offset Int32 -> Int32 # primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset Int32 -> prim Int32 # primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset Int32 -> Int32 -> prim () # primAddrIndex :: Addr# -> Offset Int32 -> Int32 # primAddrRead :: PrimMonad prim => Addr# -> Offset Int32 -> prim Int32 # primAddrWrite :: PrimMonad prim => Addr# -> Offset Int32 -> Int32 -> prim () # | |||||
NFData Int32 | |||||
Defined in Control.DeepSeq | |||||
Eq Int32 | Since: base-2.1 | ||||
Ord Int32 | Since: base-2.1 | ||||
Hashable Int32 | |||||
Defined in Data.Hashable.Class | |||||
Unbox Int32 | |||||
Defined in Data.Vector.Unboxed.Base | |||||
Lift Int32 | |||||
Vector Vector Int32 | |||||
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s Int32 -> ST s (Vector Int32) basicUnsafeThaw :: Vector Int32 -> ST s (Mutable Vector s Int32) basicLength :: Vector Int32 -> Int basicUnsafeSlice :: Int -> Int -> Vector Int32 -> Vector Int32 basicUnsafeIndexM :: Vector Int32 -> Int -> Box Int32 basicUnsafeCopy :: Mutable Vector s Int32 -> Vector Int32 -> ST s () | |||||
MVector MVector Int32 | |||||
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s Int32 -> Int basicUnsafeSlice :: Int -> Int -> MVector s Int32 -> MVector s Int32 basicOverlaps :: MVector s Int32 -> MVector s Int32 -> Bool basicUnsafeNew :: Int -> ST s (MVector s Int32) basicInitialize :: MVector s Int32 -> ST s () basicUnsafeReplicate :: Int -> Int32 -> ST s (MVector s Int32) basicUnsafeRead :: MVector s Int32 -> Int -> ST s Int32 basicUnsafeWrite :: MVector s Int32 -> Int -> Int32 -> ST s () basicClear :: MVector s Int32 -> ST s () basicSet :: MVector s Int32 -> Int32 -> ST s () basicUnsafeCopy :: MVector s Int32 -> MVector s Int32 -> ST s () basicUnsafeMove :: MVector s Int32 -> MVector s Int32 -> ST s () basicUnsafeGrow :: MVector s Int32 -> Int -> ST s (MVector s Int32) | |||||
KnownSymbol name => KnownColumn (Column name Int32) Source # | |||||
Defined in ClickHaskell | |||||
type NatNumMaxBound Int32 | |||||
Defined in Basement.Nat | |||||
type Difference Int32 | |||||
Defined in Basement.Numerical.Subtractive | |||||
type PrimSize Int32 | |||||
Defined in Basement.PrimType | |||||
newtype Vector Int32 | |||||
Defined in Data.Vector.Unboxed.Base | |||||
newtype MVector s Int32 | |||||
Defined in Data.Vector.Unboxed.Base |
64-bit signed integer type
Instances
IsChType Int64 Source # | |||||
Defined in ClickHaskell | |||||
ToQueryPart Int64 Source # | |||||
Defined in ClickHaskell Methods toQueryPart :: Int64 -> Builder Source # | |||||
Data Int64 | Since: base-4.0.0.0 | ||||
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int64 -> c Int64 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int64 # dataTypeOf :: Int64 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Int64) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int64) # gmapT :: (forall b. Data b => b -> b) -> Int64 -> Int64 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int64 -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int64 -> r # gmapQ :: (forall d. Data d => d -> u) -> Int64 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Int64 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int64 -> m Int64 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int64 -> m Int64 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int64 -> m Int64 # | |||||
Storable Int64 | Since: base-2.1 | ||||
Bits Int64 | Since: base-2.1 | ||||
Defined in GHC.Int Methods (.&.) :: Int64 -> Int64 -> Int64 # (.|.) :: Int64 -> Int64 -> Int64 # xor :: Int64 -> Int64 -> Int64 # complement :: Int64 -> Int64 # shift :: Int64 -> Int -> Int64 # rotate :: Int64 -> Int -> Int64 # setBit :: Int64 -> Int -> Int64 # clearBit :: Int64 -> Int -> Int64 # complementBit :: Int64 -> Int -> Int64 # testBit :: Int64 -> Int -> Bool # bitSizeMaybe :: Int64 -> Maybe Int # shiftL :: Int64 -> Int -> Int64 # unsafeShiftL :: Int64 -> Int -> Int64 # shiftR :: Int64 -> Int -> Int64 # unsafeShiftR :: Int64 -> Int -> Int64 # rotateL :: Int64 -> Int -> Int64 # | |||||
FiniteBits Int64 | Since: base-4.6.0.0 | ||||
Defined in GHC.Int Methods finiteBitSize :: Int64 -> Int # countLeadingZeros :: Int64 -> Int # countTrailingZeros :: Int64 -> Int # | |||||
Bounded Int64 | Since: base-2.1 | ||||
Enum Int64 | Since: base-2.1 | ||||
Ix Int64 | Since: base-2.1 | ||||
Num Int64 | Since: base-2.1 | ||||
Read Int64 | Since: base-2.1 | ||||
Integral Int64 | Since: base-2.1 | ||||
Real Int64 | Since: base-2.1 | ||||
Defined in GHC.Int Methods toRational :: Int64 -> Rational # | |||||
Show Int64 | Since: base-2.1 | ||||
PrintfArg Int64 | Since: base-2.1 | ||||
Defined in Text.Printf | |||||
BitOps Int64 | |||||
Defined in Basement.Bits | |||||
FiniteBitsOps Int64 | |||||
Defined in Basement.Bits | |||||
Subtractive Int64 | |||||
Defined in Basement.Numerical.Subtractive Associated Types
| |||||
PrimMemoryComparable Int64 | |||||
Defined in Basement.PrimType | |||||
PrimType Int64 | |||||
Defined in Basement.PrimType Associated Types
Methods primSizeInBytes :: Proxy Int64 -> CountOf Word8 # primShiftToBytes :: Proxy Int64 -> Int # primBaUIndex :: ByteArray# -> Offset Int64 -> Int64 # primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset Int64 -> prim Int64 # primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset Int64 -> Int64 -> prim () # primAddrIndex :: Addr# -> Offset Int64 -> Int64 # primAddrRead :: PrimMonad prim => Addr# -> Offset Int64 -> prim Int64 # primAddrWrite :: PrimMonad prim => Addr# -> Offset Int64 -> Int64 -> prim () # | |||||
NFData Int64 | |||||
Defined in Control.DeepSeq | |||||
Eq Int64 | Since: base-2.1 | ||||
Ord Int64 | Since: base-2.1 | ||||
Hashable Int64 | |||||
Defined in Data.Hashable.Class | |||||
Unbox Int64 | |||||
Defined in Data.Vector.Unboxed.Base | |||||
ToChType Int64 Int Source # | |||||
Lift Int64 | |||||
Vector Vector Int64 | |||||
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s Int64 -> ST s (Vector Int64) basicUnsafeThaw :: Vector Int64 -> ST s (Mutable Vector s Int64) basicLength :: Vector Int64 -> Int basicUnsafeSlice :: Int -> Int -> Vector Int64 -> Vector Int64 basicUnsafeIndexM :: Vector Int64 -> Int -> Box Int64 basicUnsafeCopy :: Mutable Vector s Int64 -> Vector Int64 -> ST s () | |||||
MVector MVector Int64 | |||||
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s Int64 -> Int basicUnsafeSlice :: Int -> Int -> MVector s Int64 -> MVector s Int64 basicOverlaps :: MVector s Int64 -> MVector s Int64 -> Bool basicUnsafeNew :: Int -> ST s (MVector s Int64) basicInitialize :: MVector s Int64 -> ST s () basicUnsafeReplicate :: Int -> Int64 -> ST s (MVector s Int64) basicUnsafeRead :: MVector s Int64 -> Int -> ST s Int64 basicUnsafeWrite :: MVector s Int64 -> Int -> Int64 -> ST s () basicClear :: MVector s Int64 -> ST s () basicSet :: MVector s Int64 -> Int64 -> ST s () basicUnsafeCopy :: MVector s Int64 -> MVector s Int64 -> ST s () basicUnsafeMove :: MVector s Int64 -> MVector s Int64 -> ST s () basicUnsafeGrow :: MVector s Int64 -> Int -> ST s (MVector s Int64) | |||||
KnownSymbol name => KnownColumn (Column name Int64) Source # | |||||
Defined in ClickHaskell | |||||
type NatNumMaxBound Int64 | |||||
Defined in Basement.Nat | |||||
type Difference Int64 | |||||
Defined in Basement.Numerical.Subtractive | |||||
type PrimSize Int64 | |||||
Defined in Basement.PrimType | |||||
newtype Vector Int64 | |||||
Defined in Data.Vector.Unboxed.Base | |||||
newtype MVector s Int64 | |||||
Defined in Data.Vector.Unboxed.Base |
Constructors
Int128 | |
Fields
|
Instances
IsChType Int128 Source # | |||||
Defined in ClickHaskell | |||||
ToQueryPart Int128 Source # | |||||
Defined in ClickHaskell Methods toQueryPart :: Int128 -> Builder Source # | |||||
Data Int128 | |||||
Defined in Data.WideWord.Int128 Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int128 -> c Int128 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int128 # toConstr :: Int128 -> Constr # dataTypeOf :: Int128 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Int128) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int128) # gmapT :: (forall b. Data b => b -> b) -> Int128 -> Int128 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int128 -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int128 -> r # gmapQ :: (forall d. Data d => d -> u) -> Int128 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Int128 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int128 -> m Int128 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int128 -> m Int128 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int128 -> m Int128 # | |||||
Storable Int128 | |||||
Bits Int128 | |||||
Defined in Data.WideWord.Int128 Methods (.&.) :: Int128 -> Int128 -> Int128 # (.|.) :: Int128 -> Int128 -> Int128 # xor :: Int128 -> Int128 -> Int128 # complement :: Int128 -> Int128 # shift :: Int128 -> Int -> Int128 # rotate :: Int128 -> Int -> Int128 # setBit :: Int128 -> Int -> Int128 # clearBit :: Int128 -> Int -> Int128 # complementBit :: Int128 -> Int -> Int128 # testBit :: Int128 -> Int -> Bool # bitSizeMaybe :: Int128 -> Maybe Int # shiftL :: Int128 -> Int -> Int128 # unsafeShiftL :: Int128 -> Int -> Int128 # shiftR :: Int128 -> Int -> Int128 # unsafeShiftR :: Int128 -> Int -> Int128 # rotateL :: Int128 -> Int -> Int128 # | |||||
FiniteBits Int128 | |||||
Defined in Data.WideWord.Int128 Methods finiteBitSize :: Int128 -> Int # countLeadingZeros :: Int128 -> Int # countTrailingZeros :: Int128 -> Int # | |||||
Bounded Int128 | |||||
Enum Int128 | |||||
Defined in Data.WideWord.Int128 | |||||
Generic Int128 | |||||
Defined in Data.WideWord.Int128 Associated Types
| |||||
Ix Int128 | |||||
Defined in Data.WideWord.Int128 | |||||
Num Int128 | |||||
Read Int128 | |||||
Integral Int128 | |||||
Defined in Data.WideWord.Int128 | |||||
Real Int128 | |||||
Defined in Data.WideWord.Int128 Methods toRational :: Int128 -> Rational # | |||||
Show Int128 | |||||
Binary Int128 | Since: wide-word-0.1.5.0 | ||||
NFData Int128 | |||||
Defined in Data.WideWord.Int128 | |||||
Eq Int128 | |||||
Ord Int128 | |||||
Hashable Int128 | |||||
Defined in Data.WideWord.Int128 | |||||
Prim Int128 | |||||
Defined in Data.WideWord.Int128 Methods sizeOfType# :: Proxy Int128 -> Int# # alignmentOfType# :: Proxy Int128 -> Int# # alignment# :: Int128 -> Int# # indexByteArray# :: ByteArray# -> Int# -> Int128 # readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Int128 #) # writeByteArray# :: MutableByteArray# s -> Int# -> Int128 -> State# s -> State# s # setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Int128 -> State# s -> State# s # indexOffAddr# :: Addr# -> Int# -> Int128 # readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Int128 #) # writeOffAddr# :: Addr# -> Int# -> Int128 -> State# s -> State# s # setOffAddr# :: Addr# -> Int# -> Int# -> Int128 -> State# s -> State# s # | |||||
KnownSymbol name => KnownColumn (Column name Int128) Source # | |||||
Defined in ClickHaskell | |||||
type Rep Int128 | |||||
Defined in Data.WideWord.Int128 type Rep Int128 = D1 ('MetaData "Int128" "Data.WideWord.Int128" "wide-word-0.1.7.0-7rMawmhFY2MEiw5A3We4xk" 'False) (C1 ('MetaCons "Int128" 'PrefixI 'True) (S1 ('MetaSel ('Just "int128Hi64") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word64) :*: S1 ('MetaSel ('Just "int128Lo64") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word64))) |
Constructors
Word128 | |
Fields
|
Instances
IsChType UInt128 Source # | |||||
Defined in ClickHaskell | |||||
ToQueryPart UInt128 Source # | |||||
Defined in ClickHaskell Methods toQueryPart :: UInt128 -> Builder Source # | |||||
Data Word128 | |||||
Defined in Data.WideWord.Word128 Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word128 -> c Word128 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word128 # toConstr :: Word128 -> Constr # dataTypeOf :: Word128 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Word128) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word128) # gmapT :: (forall b. Data b => b -> b) -> Word128 -> Word128 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word128 -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word128 -> r # gmapQ :: (forall d. Data d => d -> u) -> Word128 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Word128 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word128 -> m Word128 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word128 -> m Word128 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word128 -> m Word128 # | |||||
Storable Word128 | |||||
Bits Word128 | |||||
Defined in Data.WideWord.Word128 Methods (.&.) :: Word128 -> Word128 -> Word128 # (.|.) :: Word128 -> Word128 -> Word128 # xor :: Word128 -> Word128 -> Word128 # complement :: Word128 -> Word128 # shift :: Word128 -> Int -> Word128 # rotate :: Word128 -> Int -> Word128 # setBit :: Word128 -> Int -> Word128 # clearBit :: Word128 -> Int -> Word128 # complementBit :: Word128 -> Int -> Word128 # testBit :: Word128 -> Int -> Bool # bitSizeMaybe :: Word128 -> Maybe Int # shiftL :: Word128 -> Int -> Word128 # unsafeShiftL :: Word128 -> Int -> Word128 # shiftR :: Word128 -> Int -> Word128 # unsafeShiftR :: Word128 -> Int -> Word128 # rotateL :: Word128 -> Int -> Word128 # | |||||
FiniteBits Word128 | |||||
Defined in Data.WideWord.Word128 Methods finiteBitSize :: Word128 -> Int # countLeadingZeros :: Word128 -> Int # countTrailingZeros :: Word128 -> Int # | |||||
Bounded Word128 | |||||
Enum Word128 | |||||
Generic Word128 | |||||
Defined in Data.WideWord.Word128 Associated Types
| |||||
Ix Word128 | |||||
Defined in Data.WideWord.Word128 | |||||
Num Word128 | |||||
Read Word128 | |||||
Integral Word128 | |||||
Defined in Data.WideWord.Word128 | |||||
Real Word128 | |||||
Defined in Data.WideWord.Word128 Methods toRational :: Word128 -> Rational # | |||||
Show Word128 | |||||
Binary Word128 | Since: wide-word-0.1.5.0 | ||||
NFData Word128 | |||||
Defined in Data.WideWord.Word128 | |||||
Eq Word128 | |||||
Ord Word128 | |||||
Defined in Data.WideWord.Word128 | |||||
Hashable Word128 | |||||
Defined in Data.WideWord.Word128 | |||||
Prim Word128 | |||||
Defined in Data.WideWord.Word128 Methods sizeOfType# :: Proxy Word128 -> Int# # alignmentOfType# :: Proxy Word128 -> Int# # alignment# :: Word128 -> Int# # indexByteArray# :: ByteArray# -> Int# -> Word128 # readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Word128 #) # writeByteArray# :: MutableByteArray# s -> Int# -> Word128 -> State# s -> State# s # setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Word128 -> State# s -> State# s # indexOffAddr# :: Addr# -> Int# -> Word128 # readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Word128 #) # writeOffAddr# :: Addr# -> Int# -> Word128 -> State# s -> State# s # setOffAddr# :: Addr# -> Int# -> Int# -> Word128 -> State# s -> State# s # | |||||
ToChType UInt128 UInt64 Source # | |||||
KnownSymbol name => KnownColumn (Column name UInt128) Source # | |||||
Defined in ClickHaskell | |||||
type Rep Word128 | |||||
Defined in Data.WideWord.Word128 type Rep Word128 = D1 ('MetaData "Word128" "Data.WideWord.Word128" "wide-word-0.1.7.0-7rMawmhFY2MEiw5A3We4xk" 'False) (C1 ('MetaCons "Word128" 'PrefixI 'True) (S1 ('MetaSel ('Just "word128Hi64") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word64) :*: S1 ('MetaSel ('Just "word128Lo64") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word64))) |
data LowCardinality chType Source #
ClickHouse LowCardinality(T) column type
Instances
FromChType chType (LowCardinality chType) Source # | |
Defined in ClickHaskell Methods fromChType :: chType -> LowCardinality chType Source # | |
IsLowCardinalitySupported chType => IsChType (LowCardinality chType) Source # | |
Defined in ClickHaskell | |
ToQueryPart chType => ToQueryPart (LowCardinality chType) Source # | |
Defined in ClickHaskell Methods toQueryPart :: LowCardinality chType -> Builder Source # | |
IsString (LowCardinality ChString) Source # | |
Defined in ClickHaskell Methods fromString :: String -> LowCardinality ChString # | |
(NFData chType, IsLowCardinalitySupported chType) => NFData (LowCardinality chType) Source # | |
Defined in ClickHaskell Methods rnf :: LowCardinality chType -> () # | |
(Eq chType, IsLowCardinalitySupported chType) => Eq (LowCardinality chType) Source # | |
Defined in ClickHaskell Methods (==) :: LowCardinality chType -> LowCardinality chType -> Bool # (/=) :: LowCardinality chType -> LowCardinality chType -> Bool # | |
FromChType chType outputType => FromChType (LowCardinality chType) outputType Source # | |
Defined in ClickHaskell Methods fromChType :: LowCardinality chType -> outputType Source # | |
ToChType inputType chType => ToChType (LowCardinality inputType) chType Source # | |
Defined in ClickHaskell Methods toChType :: chType -> LowCardinality inputType Source # | |
(KnownSymbol name, IsChType (LowCardinality chType), IsLowCardinalitySupported chType) => KnownColumn (Column name (LowCardinality chType)) Source # | |
Defined in ClickHaskell Methods mkColumn :: [GetColumnType (Column name (LowCardinality chType))] -> Column (GetColumnName (Column name (LowCardinality chType))) (GetColumnType (Column name (LowCardinality chType))) | |
(KnownColumn (Column name (LowCardinality chType)), Deserializable chType, IsLowCardinalitySupported chType, TypeError ('Text "LowCardinality deserialization still unsupported") :: Constraint) => SerializableColumn (Column name (LowCardinality chType)) Source # | |
Defined in ClickHaskell Methods deserializeColumn :: ProtocolRevision -> Bool -> UVarInt -> Get (Column name (LowCardinality chType)) serializeColumn :: ProtocolRevision -> Column name (LowCardinality chType) -> Builder |
class IsChType chType => IsLowCardinalitySupported chType Source #
Instances
IsLowCardinalitySupported ChString Source # | |
Defined in ClickHaskell | |
(IsChType chType, TypeError (((((('Text "LowCardinality(" ':<>: 'ShowType chType) ':<>: 'Text ") is unsupported") ':$$: 'Text "Use one of these types:") ':$$: 'Text " ChString") ':$$: 'Text " DateTime") ':$$: 'Text " Nullable(T)") :: Constraint) => IsLowCardinalitySupported chType Source # | |
Defined in ClickHaskell | |
(IsLowCardinalitySupported chType, IsChType (Nullable chType)) => IsLowCardinalitySupported (Nullable chType) Source # | |
Defined in ClickHaskell |
ClickHouse UUID column type
Instances
IsChType UUID Source # | |
Defined in ClickHaskell | |
ToQueryPart UUID Source # | |
Defined in ClickHaskell Methods toQueryPart :: UUID -> Builder Source # | |
Bounded UUID Source # | |
Enum UUID Source # | |
Generic UUID Source # | |
Num UUID Source # | |
Show UUID Source # | |
NFData UUID Source # | |
Defined in ClickHaskell | |
Eq UUID Source # | |
ToChType UUID Word64 Source # | |
FromChType UUID (Word64, Word64) Source # | |
Defined in ClickHaskell | |
ToChType UUID (Word64, Word64) Source # | |
KnownSymbol name => KnownColumn (Column name UUID) Source # | |
Defined in ClickHaskell | |
type Rep UUID Source # | |
Defined in ClickHaskell |
ClickHouse Array column type
Constructors
MkChArray [a] |
Instances
IsChType chType => IsChType (Array chType) Source # | |
Defined in ClickHaskell | |
(IsChType chType, ToQueryPart chType) => ToQueryPart (Array chType) Source # | |
Defined in ClickHaskell Methods toQueryPart :: Array chType -> Builder Source # | |
Show a => Show (Array a) Source # | |
NFData a => NFData (Array a) Source # | |
Defined in ClickHaskell | |
Eq a => Eq (Array a) Source # | |
FromChType chType inputType => FromChType (Array chType) [inputType] Source # | |
Defined in ClickHaskell Methods fromChType :: Array chType -> [inputType] Source # | |
ToChType chType inputType => ToChType (Array chType) [inputType] Source # | |
Defined in ClickHaskell | |
KnownSymbol name => KnownColumn (Column name (Array ChString)) Source # | |
(KnownColumn (Column name (Array chType)), Deserializable chType, TypeError ('Text "Arrays deserialization still unsupported") :: Constraint) => SerializableColumn (Column name (Array chType)) Source # | |
Defined in ClickHaskell Methods deserializeColumn :: ProtocolRevision -> Bool -> UVarInt -> Get (Column name (Array chType)) serializeColumn :: ProtocolRevision -> Column name (Array chType) -> Builder |
ClickHouse String column type
Constructors
MkChString ByteString |
Instances
IsChType ChString Source # | |
Defined in ClickHaskell | |
IsLowCardinalitySupported ChString Source # | |
Defined in ClickHaskell | |
ToQueryPart ChString Source # | |
Defined in ClickHaskell Methods toQueryPart :: ChString -> Builder Source # | |
IsString ChString Source # | |
Defined in ClickHaskell Methods fromString :: String -> ChString # | |
Show ChString Source # | |
NFData ChString Source # | |
Defined in ClickHaskell | |
Eq ChString Source # | |
FromChType ChString Builder Source # | |
Defined in ClickHaskell Methods fromChType :: ChString -> Builder Source # | |
FromChType ChString ByteString Source # | |
Defined in ClickHaskell Methods fromChType :: ChString -> ByteString Source # | |
(TypeError ('Text "ChString to Text using FromChType convertion could cause exception" ':$$: 'Text "Decode ByteString manually if you are sure it's always can be decoded or replace it with ByteString") :: Constraint) => FromChType ChString Text Source # | |
Defined in ClickHaskell Methods fromChType :: ChString -> Text Source # | |
ToChType ChString Builder Source # | |
ToChType ChString ByteString Source # | |
Defined in ClickHaskell Methods toChType :: ByteString -> ChString Source # | |
ToChType ChString Text Source # | |
ToChType ChString String Source # | |
ToChType ChString Int Source # | |
IsString (LowCardinality ChString) Source # | |
Defined in ClickHaskell Methods fromString :: String -> LowCardinality ChString # | |
KnownSymbol name => KnownColumn (Column name (Array ChString)) Source # | |
KnownSymbol name => KnownColumn (Column name ChString) Source # | |
Defined in ClickHaskell |
Protocol parts
Shared
Unsigned variable-length quantity encoding
Part of protocol implementation
Instances
Bits UVarInt Source # | |
Defined in ClickHaskell Methods (.&.) :: UVarInt -> UVarInt -> UVarInt # (.|.) :: UVarInt -> UVarInt -> UVarInt # xor :: UVarInt -> UVarInt -> UVarInt # complement :: UVarInt -> UVarInt # shift :: UVarInt -> Int -> UVarInt # rotate :: UVarInt -> Int -> UVarInt # setBit :: UVarInt -> Int -> UVarInt # clearBit :: UVarInt -> Int -> UVarInt # complementBit :: UVarInt -> Int -> UVarInt # testBit :: UVarInt -> Int -> Bool # bitSizeMaybe :: UVarInt -> Maybe Int # shiftL :: UVarInt -> Int -> UVarInt # unsafeShiftL :: UVarInt -> Int -> UVarInt # shiftR :: UVarInt -> Int -> UVarInt # unsafeShiftR :: UVarInt -> Int -> UVarInt # rotateL :: UVarInt -> Int -> UVarInt # | |
Bounded UVarInt Source # | |
Enum UVarInt Source # | |
Num UVarInt Source # | |
Integral UVarInt Source # | |
Defined in ClickHaskell | |
Real UVarInt Source # | |
Defined in ClickHaskell Methods toRational :: UVarInt -> Rational # | |
Show UVarInt Source # | |
NFData UVarInt Source # | |
Defined in ClickHaskell | |
Eq UVarInt Source # | |
Ord UVarInt Source # | |
data SinceRevision a (revisionNumber :: Nat) Source #
Constructors
MkSinceRevision a | |
NotPresented |
data ProtocolRevision Source #
Instances
Num ProtocolRevision Source # | |
Defined in ClickHaskell Methods (+) :: ProtocolRevision -> ProtocolRevision -> ProtocolRevision # (-) :: ProtocolRevision -> ProtocolRevision -> ProtocolRevision # (*) :: ProtocolRevision -> ProtocolRevision -> ProtocolRevision # negate :: ProtocolRevision -> ProtocolRevision # abs :: ProtocolRevision -> ProtocolRevision # signum :: ProtocolRevision -> ProtocolRevision # fromInteger :: Integer -> ProtocolRevision # | |
Eq ProtocolRevision Source # | |
Defined in ClickHaskell Methods (==) :: ProtocolRevision -> ProtocolRevision -> Bool # (/=) :: ProtocolRevision -> ProtocolRevision -> Bool # | |
Ord ProtocolRevision Source # | |
Defined in ClickHaskell Methods compare :: ProtocolRevision -> ProtocolRevision -> Ordering # (<) :: ProtocolRevision -> ProtocolRevision -> Bool # (<=) :: ProtocolRevision -> ProtocolRevision -> Bool # (>) :: ProtocolRevision -> ProtocolRevision -> Bool # (>=) :: ProtocolRevision -> ProtocolRevision -> Bool # max :: ProtocolRevision -> ProtocolRevision -> ProtocolRevision # min :: ProtocolRevision -> ProtocolRevision -> ProtocolRevision # |
Data packet
data DataPacket Source #
Constructors
MkDataPacket | |
Fields
|
Instances
Generic DataPacket Source # | |||||
Defined in ClickHaskell Associated Types
| |||||
type Rep DataPacket Source # | |||||
Defined in ClickHaskell type Rep DataPacket = D1 ('MetaData "DataPacket" "ClickHaskell" "ClickHaskell-1.0.0-33ZTKI7EBGx7X9cBvsJ9FO" 'False) (C1 ('MetaCons "MkDataPacket" 'PrefixI 'True) ((S1 ('MetaSel ('Just "table_name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChString) :*: S1 ('MetaSel ('Just "block_info") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockInfo)) :*: (S1 ('MetaSel ('Just "columns_count") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UVarInt) :*: S1 ('MetaSel ('Just "rows_count") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UVarInt)))) |
Constructors
MkBlockInfo | |
Fields
|
Instances
Generic BlockInfo Source # | |||||
Defined in ClickHaskell Associated Types
| |||||
type Rep BlockInfo Source # | |||||
Defined in ClickHaskell type Rep BlockInfo = D1 ('MetaData "BlockInfo" "ClickHaskell" "ClickHaskell-1.0.0-33ZTKI7EBGx7X9cBvsJ9FO" 'False) (C1 ('MetaCons "MkBlockInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "field_num1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UVarInt) :*: S1 ('MetaSel ('Just "is_overflows") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UInt8)) :*: (S1 ('MetaSel ('Just "field_num2") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UVarInt) :*: (S1 ('MetaSel ('Just "bucket_num") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int32) :*: S1 ('MetaSel ('Just "eof") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UVarInt))))) |
Client
data ClientPacket where Source #
Constructors
Hello :: HelloPacket -> ClientPacket | |
Query :: QueryPacket -> ClientPacket | |
Data :: DataPacket -> ClientPacket | |
Cancel :: ClientPacket | |
Ping :: ClientPacket | |
TablesStatusRequest :: ClientPacket | |
KeepAlive :: ClientPacket | |
Scalar :: ClientPacket | |
IgnoredPartUUIDs :: ClientPacket | |
ReadTaskResponse :: ClientPacket | |
MergeTreeReadTaskResponse :: ClientPacket | |
SSHChallengeRequest :: ClientPacket | |
SSHChallengeResponse :: ClientPacket |
Instances
Generic ClientPacket Source # | |||||
Defined in ClickHaskell Associated Types
| |||||
type Rep ClientPacket Source # | |||||
Defined in ClickHaskell type Rep ClientPacket = D1 ('MetaData "ClientPacket" "ClickHaskell" "ClickHaskell-1.0.0-33ZTKI7EBGx7X9cBvsJ9FO" 'False) (((C1 ('MetaCons "Hello" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HelloPacket)) :+: (C1 ('MetaCons "Query" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 QueryPacket)) :+: C1 ('MetaCons "Data" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DataPacket)))) :+: (C1 ('MetaCons "Cancel" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Ping" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TablesStatusRequest" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "KeepAlive" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Scalar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IgnoredPartUUIDs" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ReadTaskResponse" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MergeTreeReadTaskResponse" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SSHChallengeRequest" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SSHChallengeResponse" 'PrefixI 'False) (U1 :: Type -> Type))))) |
Hello
data HelloPacket Source #
Constructors
MkHelloPacket | |
Fields |
Instances
Generic HelloPacket Source # | |||||
Defined in ClickHaskell Associated Types
| |||||
type Rep HelloPacket Source # | |||||
Defined in ClickHaskell type Rep HelloPacket = D1 ('MetaData "HelloPacket" "ClickHaskell" "ClickHaskell-1.0.0-33ZTKI7EBGx7X9cBvsJ9FO" 'False) (C1 ('MetaCons "MkHelloPacket" 'PrefixI 'True) ((S1 ('MetaSel ('Just "client_name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChString) :*: (S1 ('MetaSel ('Just "client_version_major") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UVarInt) :*: S1 ('MetaSel ('Just "client_version_minor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UVarInt))) :*: ((S1 ('MetaSel ('Just "tcp_protocol_version") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProtocolRevision) :*: S1 ('MetaSel ('Just "default_database") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChString)) :*: (S1 ('MetaSel ('Just "user") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChString) :*: S1 ('MetaSel ('Just "pass") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChString))))) |
Constructors
MkAddendum | |
Fields
|
Query
data QueryPacket Source #
Constructors
MkQueryPacket | |
Fields
|
Instances
Generic QueryPacket Source # | |||||
Defined in ClickHaskell Associated Types
| |||||
type Rep QueryPacket Source # | |||||
Defined in ClickHaskell |
data DbSettings Source #
Constructors
MkDbSettings |
data QueryParameters Source #
Constructors
MkQueryParameters |
data QueryStage Source #
Constructors
FetchColumns | |
WithMergeableState | |
Complete | |
WithMergeableStateAfterAggregation | |
WithMergeableStateAfterAggregationAndLimit |
Instances
Enum QueryStage Source # | |
Defined in ClickHaskell Methods succ :: QueryStage -> QueryStage # pred :: QueryStage -> QueryStage # toEnum :: Int -> QueryStage # fromEnum :: QueryStage -> Int # enumFrom :: QueryStage -> [QueryStage] # enumFromThen :: QueryStage -> QueryStage -> [QueryStage] # enumFromTo :: QueryStage -> QueryStage -> [QueryStage] # enumFromThenTo :: QueryStage -> QueryStage -> QueryStage -> [QueryStage] # |
data ClientInfo Source #
Constructors
MkClientInfo | |
Fields
|
Instances
Generic ClientInfo Source # | |||||
Defined in ClickHaskell Associated Types
| |||||
type Rep ClientInfo Source # | |||||
Defined in ClickHaskell |
Constructors
NoQuery | |
InitialQuery | |
SecondaryQuery |
Server
data ServerPacket where Source #
Constructors
HelloResponse :: HelloResponse -> ServerPacket | |
DataResponse :: DataPacket -> ServerPacket | |
Exception :: ExceptionPacket -> ServerPacket | |
Progress :: ProgressPacket -> ServerPacket | |
Pong :: ServerPacket | |
EndOfStream :: ServerPacket | |
ProfileInfo :: ProfileInfo -> ServerPacket | |
Totals :: ServerPacket | |
Extremes :: ServerPacket | |
TablesStatusResponse :: ServerPacket | |
Log :: ServerPacket | |
TableColumns :: TableColumns -> ServerPacket | |
UUIDs :: ServerPacket | |
ReadTaskRequest :: ServerPacket | |
ProfileEvents :: ServerPacket | |
UnknownPacket :: UVarInt -> ServerPacket |
Hello
data HelloResponse Source #
Constructors
MkHelloResponse | |
Fields
|
Instances
Generic HelloResponse Source # | |||||
Defined in ClickHaskell Associated Types
| |||||
type Rep HelloResponse Source # | |||||
Defined in ClickHaskell |
data PasswordComplexityRules Source #
Constructors
MkPasswordComplexityRules | |
Fields |
Instances
Generic PasswordComplexityRules Source # | |||||
Defined in ClickHaskell Associated Types
Methods from :: PasswordComplexityRules -> Rep PasswordComplexityRules x # to :: Rep PasswordComplexityRules x -> PasswordComplexityRules # | |||||
type Rep PasswordComplexityRules Source # | |||||
Defined in ClickHaskell type Rep PasswordComplexityRules = D1 ('MetaData "PasswordComplexityRules" "ClickHaskell" "ClickHaskell-1.0.0-33ZTKI7EBGx7X9cBvsJ9FO" 'False) (C1 ('MetaCons "MkPasswordComplexityRules" 'PrefixI 'True) (S1 ('MetaSel ('Just "original_pattern") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChString) :*: S1 ('MetaSel ('Just "exception_message") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChString))) |
Exception
data ExceptionPacket Source #
Constructors
MkExceptionPacket | |
Instances
Generic ExceptionPacket Source # | |||||
Defined in ClickHaskell Associated Types
Methods from :: ExceptionPacket -> Rep ExceptionPacket x # to :: Rep ExceptionPacket x -> ExceptionPacket # | |||||
Show ExceptionPacket Source # | |||||
Defined in ClickHaskell Methods showsPrec :: Int -> ExceptionPacket -> ShowS # show :: ExceptionPacket -> String # showList :: [ExceptionPacket] -> ShowS # | |||||
type Rep ExceptionPacket Source # | |||||
Defined in ClickHaskell type Rep ExceptionPacket = D1 ('MetaData "ExceptionPacket" "ClickHaskell" "ClickHaskell-1.0.0-33ZTKI7EBGx7X9cBvsJ9FO" 'False) (C1 ('MetaCons "MkExceptionPacket" 'PrefixI 'True) ((S1 ('MetaSel ('Just "code") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int32) :*: S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChString)) :*: (S1 ('MetaSel ('Just "message") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChString) :*: (S1 ('MetaSel ('Just "stack_trace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChString) :*: S1 ('MetaSel ('Just "nested") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UInt8))))) |
Progress
data ProgressPacket Source #
Constructors
MkProgressPacket | |
Fields
|
Instances
Generic ProgressPacket Source # | |||||
Defined in ClickHaskell Associated Types
Methods from :: ProgressPacket -> Rep ProgressPacket x # to :: Rep ProgressPacket x -> ProgressPacket # | |||||
type Rep ProgressPacket Source # | |||||
Defined in ClickHaskell |
ProfileInfo
data ProfileInfo Source #
Constructors
MkProfileInfo | |
Fields
|
Instances
Generic ProfileInfo Source # | |||||
Defined in ClickHaskell Associated Types
| |||||
type Rep ProfileInfo Source # | |||||
Defined in ClickHaskell |
TableColumns
data TableColumns Source #
Constructors
MkTableColumns | |
Fields |
Instances
Generic TableColumns Source # | |||||
Defined in ClickHaskell Associated Types
| |||||
type Rep TableColumns Source # | |||||
Defined in ClickHaskell type Rep TableColumns = D1 ('MetaData "TableColumns" "ClickHaskell" "ClickHaskell-1.0.0-33ZTKI7EBGx7X9cBvsJ9FO" 'False) (C1 ('MetaCons "MkTableColumns" 'PrefixI 'True) (S1 ('MetaSel ('Just "table_name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChString) :*: S1 ('MetaSel ('Just "table_columns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChString))) |