ClickHaskell-1.0.0: ClickHouse driver
Copyright(c) 2023 Dmitry Kovalev
LicenseBSD-3-Clause
MaintainerDmitry Kovalev
StabilityExperimental
Safe HaskellNone
LanguageHaskell2010

ClickHaskell

Description

For full documentation, visit: https://clickhaskell.dev/

Synopsis

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 

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.

data ConnectionError Source #

Errors occured on connection operations

Constructors

NoAdressResolved

Occurs when getAddrInfo returns an empty result

EstablishTimeout

Occurs on socket connection timeout

data UserError Source #

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

Instances details
Exception UserError Source # 
Instance details

Defined in ClickHaskell

Show UserError Source # 
Instance details

Defined in ClickHaskell

data InternalError Source #

These exceptions might indicate internal bugs. If you encounter one, please report it.

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 #

columns :: Builder Source #

default columns :: GenericClickHaskell record columns => Builder 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

Instances details
FromChType ChString Builder Source # 
Instance details

Defined in ClickHaskell

FromChType ChString ByteString Source # 
Instance details

Defined in ClickHaskell

(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 # 
Instance details

Defined in ClickHaskell

(IsChType chType, chType ~ inputType) => FromChType chType inputType Source # 
Instance details

Defined in ClickHaskell

Methods

fromChType :: chType -> inputType Source #

FromChType chType (LowCardinality chType) Source # 
Instance details

Defined in ClickHaskell

Methods

fromChType :: chType -> LowCardinality chType Source #

FromChType UUID (Word64, Word64) Source # 
Instance details

Defined in ClickHaskell

FromChType (DateTime tz) Word32 Source # 
Instance details

Defined in ClickHaskell

FromChType (DateTime tz) UTCTime Source # 
Instance details

Defined in ClickHaskell

FromChType chType outputType => FromChType (LowCardinality chType) outputType Source # 
Instance details

Defined in ClickHaskell

Methods

fromChType :: LowCardinality chType -> outputType Source #

FromChType chType inputType => FromChType (Array chType) [inputType] Source # 
Instance details

Defined in ClickHaskell

Methods

fromChType :: Array chType -> [inputType] Source #

FromChType chType inputType => FromChType (Nullable chType) (Nullable inputType) Source # 
Instance details

Defined in ClickHaskell

Methods

fromChType :: Nullable chType -> Nullable inputType Source #

FromChType (DateTime64 precision tz) Word64 Source # 
Instance details

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 #

Methods

toChType :: inputType -> chType Source #

Instances

Instances details
ToChType ChString Builder Source # 
Instance details

Defined in ClickHaskell

ToChType ChString ByteString Source # 
Instance details

Defined in ClickHaskell

ToChType ChString Text Source # 
Instance details

Defined in ClickHaskell

ToChType ChString String Source # 
Instance details

Defined in ClickHaskell

ToChType ChString Int Source # 
Instance details

Defined in ClickHaskell

ToChType UInt128 UInt64 Source # 
Instance details

Defined in ClickHaskell

ToChType UUID Word64 Source # 
Instance details

Defined in ClickHaskell

Methods

toChType :: Word64 -> UUID Source #

ToChType Int64 Int Source # 
Instance details

Defined in ClickHaskell

Methods

toChType :: Int -> Int64 Source #

(IsChType chType, chType ~ inputType) => ToChType chType inputType Source # 
Instance details

Defined in ClickHaskell

Methods

toChType :: inputType -> chType Source #

ToChType UUID (Word64, Word64) Source # 
Instance details

Defined in ClickHaskell

Methods

toChType :: (Word64, Word64) -> UUID Source #

ToChType (DateTime tz) Word32 Source # 
Instance details

Defined in ClickHaskell

Methods

toChType :: Word32 -> DateTime tz Source #

ToChType (DateTime tz) UTCTime Source # 
Instance details

Defined in ClickHaskell

Methods

toChType :: UTCTime -> DateTime tz Source #

ToChType (DateTime tz) ZonedTime Source # 
Instance details

Defined in ClickHaskell

ToChType inputType chType => ToChType (LowCardinality inputType) chType Source # 
Instance details

Defined in ClickHaskell

Methods

toChType :: chType -> LowCardinality inputType Source #

ToChType chType inputType => ToChType (Array chType) [inputType] Source # 
Instance details

Defined in ClickHaskell

Methods

toChType :: [inputType] -> Array chType Source #

ToChType inputType chType => ToChType (Nullable inputType) (Nullable chType) Source # 
Instance details

Defined in ClickHaskell

Methods

toChType :: Nullable chType -> Nullable inputType Source #

ToChType (DateTime64 precision tz) Word64 Source # 
Instance details

Defined in ClickHaskell

Methods

toChType :: Word64 -> DateTime64 precision tz Source #

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

Shared

data Column (name :: Symbol) chType Source #

Column declaration

For example:

type MyColumn = Column "myColumn" ChString

Instances

Instances details
KnownSymbol name => KnownColumn (Column name (Array ChString)) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name (Array ChString))] -> Column (GetColumnName (Column name (Array ChString))) (GetColumnType (Column name (Array ChString)))

KnownSymbol name => KnownColumn (Column name ChString) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name ChString)] -> Column (GetColumnName (Column name ChString)) (GetColumnType (Column name ChString))

(KnownSymbol name, IsChType (DateTime tz)) => KnownColumn (Column name (DateTime tz)) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name (DateTime tz))] -> Column (GetColumnName (Column name (DateTime tz))) (GetColumnType (Column name (DateTime tz)))

(KnownSymbol name, IsChType (DateTime64 precision tz)) => KnownColumn (Column name (DateTime64 precision tz)) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name (DateTime64 precision tz))] -> Column (GetColumnName (Column name (DateTime64 precision tz))) (GetColumnType (Column name (DateTime64 precision tz)))

(KnownSymbol name, IsChType (LowCardinality chType), IsLowCardinalitySupported chType) => KnownColumn (Column name (LowCardinality chType)) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name (LowCardinality chType))] -> Column (GetColumnName (Column name (LowCardinality chType))) (GetColumnType (Column name (LowCardinality chType)))

(KnownSymbol name, IsChType chType, IsChType (Nullable chType)) => KnownColumn (Column name (Nullable chType)) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name (Nullable chType))] -> Column (GetColumnName (Column name (Nullable chType))) (GetColumnType (Column name (Nullable chType)))

KnownSymbol name => KnownColumn (Column name UInt128) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name UInt128)] -> Column (GetColumnName (Column name UInt128)) (GetColumnType (Column name UInt128))

KnownSymbol name => KnownColumn (Column name UInt16) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name UInt16)] -> Column (GetColumnName (Column name UInt16)) (GetColumnType (Column name UInt16))

KnownSymbol name => KnownColumn (Column name UInt32) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name UInt32)] -> Column (GetColumnName (Column name UInt32)) (GetColumnType (Column name UInt32))

KnownSymbol name => KnownColumn (Column name UInt64) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name UInt64)] -> Column (GetColumnName (Column name UInt64)) (GetColumnType (Column name UInt64))

KnownSymbol name => KnownColumn (Column name UInt8) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name UInt8)] -> Column (GetColumnName (Column name UInt8)) (GetColumnType (Column name UInt8))

KnownSymbol name => KnownColumn (Column name UUID) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name UUID)] -> Column (GetColumnName (Column name UUID)) (GetColumnType (Column name UUID))

KnownSymbol name => KnownColumn (Column name Int16) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name Int16)] -> Column (GetColumnName (Column name Int16)) (GetColumnType (Column name Int16))

KnownSymbol name => KnownColumn (Column name Int32) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name Int32)] -> Column (GetColumnName (Column name Int32)) (GetColumnType (Column name Int32))

KnownSymbol name => KnownColumn (Column name Int64) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name Int64)] -> Column (GetColumnName (Column name Int64)) (GetColumnType (Column name Int64))

KnownSymbol name => KnownColumn (Column name Int8) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name Int8)] -> Column (GetColumnName (Column name Int8)) (GetColumnType (Column name Int8))

KnownSymbol name => KnownColumn (Column name Int128) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name Int128)] -> Column (GetColumnName (Column name Int128)) (GetColumnType (Column name Int128))

(KnownColumn (Column name (Array chType)), Deserializable chType, TypeError ('Text "Arrays deserialization still unsupported") :: Constraint) => SerializableColumn (Column name (Array chType)) Source # 
Instance details

Defined in ClickHaskell

(KnownColumn (Column name (LowCardinality chType)), Deserializable chType, IsLowCardinalitySupported chType, TypeError ('Text "LowCardinality deserialization still unsupported") :: Constraint) => SerializableColumn (Column name (LowCardinality chType)) Source # 
Instance details

Defined in ClickHaskell

(KnownColumn (Column name (Nullable chType)), Deserializable chType, Serializable chType, IsChType chType) => SerializableColumn (Column name (Nullable chType)) Source # 
Instance details

Defined in ClickHaskell

(KnownColumn (Column name chType), Deserializable chType, Serializable chType, IsChType chType) => SerializableColumn (Column name chType) Source # 
Instance details

Defined in ClickHaskell

class (IsChType (GetColumnType column), KnownSymbol (GetColumnName column)) => KnownColumn column Source #

Minimal complete definition

mkColumn

Instances

Instances details
KnownSymbol name => KnownColumn (Column name (Array ChString)) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name (Array ChString))] -> Column (GetColumnName (Column name (Array ChString))) (GetColumnType (Column name (Array ChString)))

KnownSymbol name => KnownColumn (Column name ChString) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name ChString)] -> Column (GetColumnName (Column name ChString)) (GetColumnType (Column name ChString))

(KnownSymbol name, IsChType (DateTime tz)) => KnownColumn (Column name (DateTime tz)) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name (DateTime tz))] -> Column (GetColumnName (Column name (DateTime tz))) (GetColumnType (Column name (DateTime tz)))

(KnownSymbol name, IsChType (DateTime64 precision tz)) => KnownColumn (Column name (DateTime64 precision tz)) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name (DateTime64 precision tz))] -> Column (GetColumnName (Column name (DateTime64 precision tz))) (GetColumnType (Column name (DateTime64 precision tz)))

(KnownSymbol name, IsChType (LowCardinality chType), IsLowCardinalitySupported chType) => KnownColumn (Column name (LowCardinality chType)) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name (LowCardinality chType))] -> Column (GetColumnName (Column name (LowCardinality chType))) (GetColumnType (Column name (LowCardinality chType)))

(KnownSymbol name, IsChType chType, IsChType (Nullable chType)) => KnownColumn (Column name (Nullable chType)) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name (Nullable chType))] -> Column (GetColumnName (Column name (Nullable chType))) (GetColumnType (Column name (Nullable chType)))

KnownSymbol name => KnownColumn (Column name UInt128) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name UInt128)] -> Column (GetColumnName (Column name UInt128)) (GetColumnType (Column name UInt128))

KnownSymbol name => KnownColumn (Column name UInt16) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name UInt16)] -> Column (GetColumnName (Column name UInt16)) (GetColumnType (Column name UInt16))

KnownSymbol name => KnownColumn (Column name UInt32) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name UInt32)] -> Column (GetColumnName (Column name UInt32)) (GetColumnType (Column name UInt32))

KnownSymbol name => KnownColumn (Column name UInt64) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name UInt64)] -> Column (GetColumnName (Column name UInt64)) (GetColumnType (Column name UInt64))

KnownSymbol name => KnownColumn (Column name UInt8) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name UInt8)] -> Column (GetColumnName (Column name UInt8)) (GetColumnType (Column name UInt8))

KnownSymbol name => KnownColumn (Column name UUID) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name UUID)] -> Column (GetColumnName (Column name UUID)) (GetColumnType (Column name UUID))

KnownSymbol name => KnownColumn (Column name Int16) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name Int16)] -> Column (GetColumnName (Column name Int16)) (GetColumnType (Column name Int16))

KnownSymbol name => KnownColumn (Column name Int32) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name Int32)] -> Column (GetColumnName (Column name Int32)) (GetColumnType (Column name Int32))

KnownSymbol name => KnownColumn (Column name Int64) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name Int64)] -> Column (GetColumnName (Column name Int64)) (GetColumnType (Column name Int64))

KnownSymbol name => KnownColumn (Column name Int8) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name Int8)] -> Column (GetColumnName (Column name Int8)) (GetColumnType (Column name Int8))

KnownSymbol name => KnownColumn (Column name Int128) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name Int128)] -> Column (GetColumnName (Column name Int128)) (GetColumnType (Column name Int128))

class SerializableColumn column Source #

Minimal complete definition

deserializeColumn, serializeColumn

Instances

Instances details
(KnownColumn (Column name (Array chType)), Deserializable chType, TypeError ('Text "Arrays deserialization still unsupported") :: Constraint) => SerializableColumn (Column name (Array chType)) Source # 
Instance details

Defined in ClickHaskell

(KnownColumn (Column name (LowCardinality chType)), Deserializable chType, IsLowCardinalitySupported chType, TypeError ('Text "LowCardinality deserialization still unsupported") :: Constraint) => SerializableColumn (Column name (LowCardinality chType)) Source # 
Instance details

Defined in ClickHaskell

(KnownColumn (Column name (Nullable chType)), Deserializable chType, Serializable chType, IsChType chType) => SerializableColumn (Column name (Nullable chType)) Source # 
Instance details

Defined in ClickHaskell

(KnownColumn (Column name chType), Deserializable chType, Serializable chType, IsChType chType) => SerializableColumn (Column name chType) Source # 
Instance details

Defined in ClickHaskell

data Table (name :: Symbol) (columns :: [Type]) Source #

data View (name :: Symbol) (columns :: [Type]) (parameters :: [Type]) Source #

Query

class ToQueryPart chType where Source #

Methods

toQueryPart :: chType -> Builder Source #

Instances

Instances details
ToQueryPart ChString Source # 
Instance details

Defined in ClickHaskell

ToQueryPart UInt128 Source # 
Instance details

Defined in ClickHaskell

ToQueryPart UInt16 Source # 
Instance details

Defined in ClickHaskell

ToQueryPart UInt32 Source # 
Instance details

Defined in ClickHaskell

ToQueryPart UInt64 Source # 
Instance details

Defined in ClickHaskell

ToQueryPart UInt8 Source # 
Instance details

Defined in ClickHaskell

ToQueryPart UUID Source # 
Instance details

Defined in ClickHaskell

ToQueryPart Int16 Source # 
Instance details

Defined in ClickHaskell

ToQueryPart Int32 Source # 
Instance details

Defined in ClickHaskell

ToQueryPart Int64 Source # 
Instance details

Defined in ClickHaskell

ToQueryPart Int8 Source # 
Instance details

Defined in ClickHaskell

ToQueryPart Int128 Source # 
Instance details

Defined in ClickHaskell

(IsChType chType, ToQueryPart chType) => ToQueryPart (Array chType) Source # 
Instance details

Defined in ClickHaskell

Methods

toQueryPart :: Array chType -> Builder Source #

ToQueryPart (DateTime tz) Source # 
Instance details

Defined in ClickHaskell

ToQueryPart chType => ToQueryPart (LowCardinality chType) Source # 
Instance details

Defined in ClickHaskell

ToQueryPart chType => ToQueryPart (Nullable chType) Source # 
Instance details

Defined in ClickHaskell

Methods

toQueryPart :: Nullable chType -> Builder Source #

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 Parameter (name :: Symbol) chType 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

Instances details
IsChType ChString Source # 
Instance details

Defined in ClickHaskell

IsChType UInt128 Source # 
Instance details

Defined in ClickHaskell

IsChType UInt16 Source # 
Instance details

Defined in ClickHaskell

IsChType UInt32 Source # 
Instance details

Defined in ClickHaskell

IsChType UInt64 Source # 
Instance details

Defined in ClickHaskell

IsChType UInt8 Source # 
Instance details

Defined in ClickHaskell

IsChType UUID Source # 
Instance details

Defined in ClickHaskell

IsChType Int16 Source # 
Instance details

Defined in ClickHaskell

IsChType Int32 Source # 
Instance details

Defined in ClickHaskell

IsChType Int64 Source # 
Instance details

Defined in ClickHaskell

IsChType Int8 Source # 
Instance details

Defined in ClickHaskell

IsChType Int128 Source # 
Instance details

Defined in ClickHaskell

IsChType chType => IsChType (Array chType) Source # 
Instance details

Defined in ClickHaskell

KnownSymbol (DateTimeTypeName tz) => IsChType (DateTime tz) Source # 
Instance details

Defined in ClickHaskell

IsLowCardinalitySupported chType => IsChType (LowCardinality chType) Source # 
Instance details

Defined in ClickHaskell

IsChType chType => IsChType (Nullable chType) Source # 
Instance details

Defined in ClickHaskell

(KnownSymbol tz, KnownNat precision) => IsChType (DateTime64 precision tz) Source # 
Instance details

Defined in ClickHaskell

newtype DateTime (tz :: Symbol) Source #

ClickHouse DateTime column type (paramtrized with timezone)

>>> chTypeName @(DateTime "")
"DateTime"
>>> chTypeName @(DateTime "UTC")
"DateTime('UTC')"

Constructors

MkDateTime Word32 

Instances

Instances details
KnownSymbol (DateTimeTypeName tz) => IsChType (DateTime tz) Source # 
Instance details

Defined in ClickHaskell

ToQueryPart (DateTime tz) Source # 
Instance details

Defined in ClickHaskell

Bits (DateTime tz) Source # 
Instance details

Defined in ClickHaskell

Methods

(.&.) :: DateTime tz -> DateTime tz -> DateTime tz #

(.|.) :: DateTime tz -> DateTime tz -> DateTime tz #

xor :: DateTime tz -> DateTime tz -> DateTime tz #

complement :: DateTime tz -> DateTime tz #

shift :: DateTime tz -> Int -> DateTime tz #

rotate :: DateTime tz -> Int -> DateTime tz #

zeroBits :: DateTime tz #

bit :: Int -> DateTime tz #

setBit :: DateTime tz -> Int -> DateTime tz #

clearBit :: DateTime tz -> Int -> DateTime tz #

complementBit :: DateTime tz -> Int -> DateTime tz #

testBit :: DateTime tz -> Int -> Bool #

bitSizeMaybe :: DateTime tz -> Maybe Int #

bitSize :: DateTime tz -> Int #

isSigned :: DateTime tz -> Bool #

shiftL :: DateTime tz -> Int -> DateTime tz #

unsafeShiftL :: DateTime tz -> Int -> DateTime tz #

shiftR :: DateTime tz -> Int -> DateTime tz #

unsafeShiftR :: DateTime tz -> Int -> DateTime tz #

rotateL :: DateTime tz -> Int -> DateTime tz #

rotateR :: DateTime tz -> Int -> DateTime tz #

popCount :: DateTime tz -> Int #

Bounded (DateTime tz) Source # 
Instance details

Defined in ClickHaskell

Methods

minBound :: DateTime tz #

maxBound :: DateTime tz #

Enum (DateTime tz) Source # 
Instance details

Defined in ClickHaskell

Methods

succ :: DateTime tz -> DateTime tz #

pred :: DateTime tz -> DateTime tz #

toEnum :: Int -> DateTime tz #

fromEnum :: DateTime tz -> Int #

enumFrom :: DateTime tz -> [DateTime tz] #

enumFromThen :: DateTime tz -> DateTime tz -> [DateTime tz] #

enumFromTo :: DateTime tz -> DateTime tz -> [DateTime tz] #

enumFromThenTo :: DateTime tz -> DateTime tz -> DateTime tz -> [DateTime tz] #

Num (DateTime tz) Source # 
Instance details

Defined in ClickHaskell

Methods

(+) :: DateTime tz -> DateTime tz -> DateTime tz #

(-) :: DateTime tz -> DateTime tz -> DateTime tz #

(*) :: DateTime tz -> DateTime tz -> DateTime tz #

negate :: DateTime tz -> DateTime tz #

abs :: DateTime tz -> DateTime tz #

signum :: DateTime tz -> DateTime tz #

fromInteger :: Integer -> DateTime tz #

Integral (DateTime tz) Source # 
Instance details

Defined in ClickHaskell

Methods

quot :: DateTime tz -> DateTime tz -> DateTime tz #

rem :: DateTime tz -> DateTime tz -> DateTime tz #

div :: DateTime tz -> DateTime tz -> DateTime tz #

mod :: DateTime tz -> DateTime tz -> DateTime tz #

quotRem :: DateTime tz -> DateTime tz -> (DateTime tz, DateTime tz) #

divMod :: DateTime tz -> DateTime tz -> (DateTime tz, DateTime tz) #

toInteger :: DateTime tz -> Integer #

Real (DateTime tz) Source # 
Instance details

Defined in ClickHaskell

Methods

toRational :: DateTime tz -> Rational #

Show (DateTime tz) Source # 
Instance details

Defined in ClickHaskell

Methods

showsPrec :: Int -> DateTime tz -> ShowS #

show :: DateTime tz -> String #

showList :: [DateTime tz] -> ShowS #

NFData (DateTime tz) Source # 
Instance details

Defined in ClickHaskell

Methods

rnf :: DateTime tz -> () #

Eq (DateTime tz) Source # 
Instance details

Defined in ClickHaskell

Methods

(==) :: DateTime tz -> DateTime tz -> Bool #

(/=) :: DateTime tz -> DateTime tz -> Bool #

Ord (DateTime tz) Source # 
Instance details

Defined in ClickHaskell

Methods

compare :: 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 #

max :: DateTime tz -> DateTime tz -> DateTime tz #

min :: DateTime tz -> DateTime tz -> DateTime tz #

FromChType (DateTime tz) Word32 Source # 
Instance details

Defined in ClickHaskell

FromChType (DateTime tz) UTCTime Source # 
Instance details

Defined in ClickHaskell

ToChType (DateTime tz) Word32 Source # 
Instance details

Defined in ClickHaskell

Methods

toChType :: Word32 -> DateTime tz Source #

ToChType (DateTime tz) UTCTime Source # 
Instance details

Defined in ClickHaskell

Methods

toChType :: UTCTime -> DateTime tz Source #

ToChType (DateTime tz) ZonedTime Source # 
Instance details

Defined in ClickHaskell

(KnownSymbol name, IsChType (DateTime tz)) => KnownColumn (Column name (DateTime tz)) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name (DateTime tz))] -> Column (GetColumnName (Column name (DateTime tz))) (GetColumnType (Column name (DateTime tz)))

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

Instances details
(KnownSymbol tz, KnownNat precision) => IsChType (DateTime64 precision tz) Source # 
Instance details

Defined in ClickHaskell

(KnownSymbol name, IsChType (DateTime64 precision tz)) => KnownColumn (Column name (DateTime64 precision tz)) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

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 # 
Instance details

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 # 
Instance details

Defined in ClickHaskell

Methods

minBound :: DateTime64 precision tz #

maxBound :: DateTime64 precision tz #

Enum (DateTime64 precision tz) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in ClickHaskell

Methods

toRational :: DateTime64 precision tz -> Rational #

Show (DateTime64 precision tz) Source # 
Instance details

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 # 
Instance details

Defined in ClickHaskell

Methods

rnf :: DateTime64 precision tz -> () #

Eq (DateTime64 precision tz) Source # 
Instance details

Defined in ClickHaskell

Methods

(==) :: DateTime64 precision tz -> DateTime64 precision tz -> Bool #

(/=) :: DateTime64 precision tz -> DateTime64 precision tz -> Bool #

Ord (DateTime64 precision tz) Source # 
Instance details

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 # 
Instance details

Defined in ClickHaskell

Methods

fromChType :: DateTime64 precision tz -> Word64 Source #

ToChType (DateTime64 precision tz) Word64 Source # 
Instance details

Defined in ClickHaskell

Methods

toChType :: Word64 -> DateTime64 precision tz Source #

data Int8 #

8-bit signed integer type

Instances

Instances details
IsChType Int8 Source # 
Instance details

Defined in ClickHaskell

ToQueryPart Int8 Source # 
Instance details

Defined in ClickHaskell

Data Int8

Since: base-4.0.0.0

Instance details

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 #

toConstr :: Int8 -> Constr #

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

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int8 -> Int #

alignment :: Int8 -> Int #

peekElemOff :: Ptr Int8 -> Int -> IO Int8 #

pokeElemOff :: Ptr Int8 -> Int -> Int8 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int8 #

pokeByteOff :: Ptr b -> Int -> Int8 -> IO () #

peek :: Ptr Int8 -> IO Int8 #

poke :: Ptr Int8 -> Int8 -> IO () #

Bits Int8

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBits Int8

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

Bounded Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

succ :: Int8 -> Int8 #

pred :: Int8 -> Int8 #

toEnum :: Int -> Int8 #

fromEnum :: Int8 -> Int #

enumFrom :: Int8 -> [Int8] #

enumFromThen :: Int8 -> Int8 -> [Int8] #

enumFromTo :: Int8 -> Int8 -> [Int8] #

enumFromThenTo :: Int8 -> Int8 -> Int8 -> [Int8] #

Ix Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

range :: (Int8, Int8) -> [Int8] #

index :: (Int8, Int8) -> Int8 -> Int #

unsafeIndex :: (Int8, Int8) -> Int8 -> Int #

inRange :: (Int8, Int8) -> Int8 -> Bool #

rangeSize :: (Int8, Int8) -> Int #

unsafeRangeSize :: (Int8, Int8) -> Int #

Num Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

(+) :: Int8 -> Int8 -> Int8 #

(-) :: Int8 -> Int8 -> Int8 #

(*) :: Int8 -> Int8 -> Int8 #

negate :: Int8 -> Int8 #

abs :: Int8 -> Int8 #

signum :: Int8 -> Int8 #

fromInteger :: Integer -> Int8 #

Read Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Integral Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

quot :: Int8 -> Int8 -> Int8 #

rem :: Int8 -> Int8 -> Int8 #

div :: Int8 -> Int8 -> Int8 #

mod :: Int8 -> Int8 -> Int8 #

quotRem :: Int8 -> Int8 -> (Int8, Int8) #

divMod :: Int8 -> Int8 -> (Int8, Int8) #

toInteger :: Int8 -> Integer #

Real Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

toRational :: Int8 -> Rational #

Show Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int8 -> ShowS #

show :: Int8 -> String #

showList :: [Int8] -> ShowS #

PrintfArg Int8

Since: base-2.1

Instance details

Defined in Text.Printf

BitOps Int8 
Instance details

Defined in Basement.Bits

FiniteBitsOps Int8 
Instance details

Defined in Basement.Bits

Subtractive Int8 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Int8 
Instance details

Defined in Basement.Numerical.Subtractive

Methods

(-) :: Int8 -> Int8 -> Difference Int8 #

PrimMemoryComparable Int8 
Instance details

Defined in Basement.PrimType

PrimType Int8 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Int8 
Instance details

Defined in Basement.PrimType

type PrimSize Int8 = 1
NFData Int8 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int8 -> () #

Eq Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

(==) :: Int8 -> Int8 -> Bool #

(/=) :: Int8 -> Int8 -> Bool #

Ord Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

compare :: Int8 -> Int8 -> Ordering #

(<) :: Int8 -> Int8 -> Bool #

(<=) :: Int8 -> Int8 -> Bool #

(>) :: Int8 -> Int8 -> Bool #

(>=) :: Int8 -> Int8 -> Bool #

max :: Int8 -> Int8 -> Int8 #

min :: Int8 -> Int8 -> Int8 #

Hashable Int8 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int8 -> Int #

hash :: Int8 -> Int #

Unbox Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

Lift Int8 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Int8 -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Int8 -> Code m Int8 #

Vector Vector Int8 
Instance details

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 ()

elemseq :: Vector Int8 -> Int8 -> b -> b

MVector MVector Int8 
Instance details

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 # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name Int8)] -> Column (GetColumnName (Column name Int8)) (GetColumnType (Column name Int8))

type NatNumMaxBound Int8 
Instance details

Defined in Basement.Nat

type NatNumMaxBound Int8 = 127
type Difference Int8 
Instance details

Defined in Basement.Numerical.Subtractive

type PrimSize Int8 
Instance details

Defined in Basement.PrimType

type PrimSize Int8 = 1
newtype Vector Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int8 = V_Int8 (Vector Int8)
newtype MVector s Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int8 = MV_Int8 (MVector s Int8)

data Int16 #

16-bit signed integer type

Instances

Instances details
IsChType Int16 Source # 
Instance details

Defined in ClickHaskell

ToQueryPart Int16 Source # 
Instance details

Defined in ClickHaskell

Data Int16

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int16 -> c Int16 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int16 #

toConstr :: Int16 -> Constr #

dataTypeOf :: Int16 -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Int16) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int16) #

gmapT :: (forall b. Data b => b -> b) -> Int16 -> Int16 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int16 -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int16 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Int16 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Int16 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int16 -> m Int16 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int16 -> m Int16 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int16 -> m Int16 #

Storable Int16

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int16 -> Int #

alignment :: Int16 -> Int #

peekElemOff :: Ptr Int16 -> Int -> IO Int16 #

pokeElemOff :: Ptr Int16 -> Int -> Int16 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int16 #

pokeByteOff :: Ptr b -> Int -> Int16 -> IO () #

peek :: Ptr Int16 -> IO Int16 #

poke :: Ptr Int16 -> Int16 -> IO () #

Bits Int16

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBits Int16

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

Bounded Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Ix Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Num Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Read Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Integral Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Real Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

toRational :: Int16 -> Rational #

Show Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int16 -> ShowS #

show :: Int16 -> String #

showList :: [Int16] -> ShowS #

PrintfArg Int16

Since: base-2.1

Instance details

Defined in Text.Printf

BitOps Int16 
Instance details

Defined in Basement.Bits

FiniteBitsOps Int16 
Instance details

Defined in Basement.Bits

Subtractive Int16 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Int16 
Instance details

Defined in Basement.Numerical.Subtractive

Methods

(-) :: Int16 -> Int16 -> Difference Int16 #

PrimMemoryComparable Int16 
Instance details

Defined in Basement.PrimType

PrimType Int16 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Int16 
Instance details

Defined in Basement.PrimType

type PrimSize Int16 = 2
NFData Int16 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int16 -> () #

Eq Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

(==) :: Int16 -> Int16 -> Bool #

(/=) :: Int16 -> Int16 -> Bool #

Ord Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

compare :: Int16 -> Int16 -> Ordering #

(<) :: Int16 -> Int16 -> Bool #

(<=) :: Int16 -> Int16 -> Bool #

(>) :: Int16 -> Int16 -> Bool #

(>=) :: Int16 -> Int16 -> Bool #

max :: Int16 -> Int16 -> Int16 #

min :: Int16 -> Int16 -> Int16 #

Hashable Int16 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int16 -> Int #

hash :: Int16 -> Int #

Unbox Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

Lift Int16 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Int16 -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Int16 -> Code m Int16 #

Vector Vector Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: Mutable Vector s Int16 -> ST s (Vector Int16)

basicUnsafeThaw :: Vector Int16 -> ST s (Mutable Vector s Int16)

basicLength :: Vector Int16 -> Int

basicUnsafeSlice :: Int -> Int -> Vector Int16 -> Vector Int16

basicUnsafeIndexM :: Vector Int16 -> Int -> Box Int16

basicUnsafeCopy :: Mutable Vector s Int16 -> Vector Int16 -> ST s ()

elemseq :: Vector Int16 -> Int16 -> b -> b

MVector MVector Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s Int16 -> Int

basicUnsafeSlice :: Int -> Int -> MVector s Int16 -> MVector s Int16

basicOverlaps :: MVector s Int16 -> MVector s Int16 -> Bool

basicUnsafeNew :: Int -> ST s (MVector s Int16)

basicInitialize :: MVector s Int16 -> ST s ()

basicUnsafeReplicate :: Int -> Int16 -> ST s (MVector s Int16)

basicUnsafeRead :: MVector s Int16 -> Int -> ST s Int16

basicUnsafeWrite :: MVector s Int16 -> Int -> Int16 -> ST s ()

basicClear :: MVector s Int16 -> ST s ()

basicSet :: MVector s Int16 -> Int16 -> ST s ()

basicUnsafeCopy :: MVector s Int16 -> MVector s Int16 -> ST s ()

basicUnsafeMove :: MVector s Int16 -> MVector s Int16 -> ST s ()

basicUnsafeGrow :: MVector s Int16 -> Int -> ST s (MVector s Int16)

KnownSymbol name => KnownColumn (Column name Int16) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name Int16)] -> Column (GetColumnName (Column name Int16)) (GetColumnType (Column name Int16))

type NatNumMaxBound Int16 
Instance details

Defined in Basement.Nat

type NatNumMaxBound Int16 = 32767
type Difference Int16 
Instance details

Defined in Basement.Numerical.Subtractive

type PrimSize Int16 
Instance details

Defined in Basement.PrimType

type PrimSize Int16 = 2
newtype Vector Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int16 = V_Int16 (Vector Int16)
newtype MVector s Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int16 = MV_Int16 (MVector s Int16)

data Int32 #

32-bit signed integer type

Instances

Instances details
IsChType Int32 Source # 
Instance details

Defined in ClickHaskell

ToQueryPart Int32 Source # 
Instance details

Defined in ClickHaskell

Data Int32

Since: base-4.0.0.0

Instance details

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 #

toConstr :: Int32 -> Constr #

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

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int32 -> Int #

alignment :: Int32 -> Int #

peekElemOff :: Ptr Int32 -> Int -> IO Int32 #

pokeElemOff :: Ptr Int32 -> Int -> Int32 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int32 #

pokeByteOff :: Ptr b -> Int -> Int32 -> IO () #

peek :: Ptr Int32 -> IO Int32 #

poke :: Ptr Int32 -> Int32 -> IO () #

Bits Int32

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBits Int32

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

Bounded Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Ix Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Num Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Read Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Integral Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Real Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

toRational :: Int32 -> Rational #

Show Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int32 -> ShowS #

show :: Int32 -> String #

showList :: [Int32] -> ShowS #

PrintfArg Int32

Since: base-2.1

Instance details

Defined in Text.Printf

BitOps Int32 
Instance details

Defined in Basement.Bits

FiniteBitsOps Int32 
Instance details

Defined in Basement.Bits

Subtractive Int32 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Int32 
Instance details

Defined in Basement.Numerical.Subtractive

Methods

(-) :: Int32 -> Int32 -> Difference Int32 #

PrimMemoryComparable Int32 
Instance details

Defined in Basement.PrimType

PrimType Int32 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Int32 
Instance details

Defined in Basement.PrimType

type PrimSize Int32 = 4
NFData Int32 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int32 -> () #

Eq Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

(==) :: Int32 -> Int32 -> Bool #

(/=) :: Int32 -> Int32 -> Bool #

Ord Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

compare :: Int32 -> Int32 -> Ordering #

(<) :: Int32 -> Int32 -> Bool #

(<=) :: Int32 -> Int32 -> Bool #

(>) :: Int32 -> Int32 -> Bool #

(>=) :: Int32 -> Int32 -> Bool #

max :: Int32 -> Int32 -> Int32 #

min :: Int32 -> Int32 -> Int32 #

Hashable Int32 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int32 -> Int #

hash :: Int32 -> Int #

Unbox Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

Lift Int32 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Int32 -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Int32 -> Code m Int32 #

Vector Vector Int32 
Instance details

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 ()

elemseq :: Vector Int32 -> Int32 -> b -> b

MVector MVector Int32 
Instance details

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 # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name Int32)] -> Column (GetColumnName (Column name Int32)) (GetColumnType (Column name Int32))

type NatNumMaxBound Int32 
Instance details

Defined in Basement.Nat

type NatNumMaxBound Int32 = 2147483647
type Difference Int32 
Instance details

Defined in Basement.Numerical.Subtractive

type PrimSize Int32 
Instance details

Defined in Basement.PrimType

type PrimSize Int32 = 4
newtype Vector Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int32 = V_Int32 (Vector Int32)
newtype MVector s Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int32 = MV_Int32 (MVector s Int32)

data Int64 #

64-bit signed integer type

Instances

Instances details
IsChType Int64 Source # 
Instance details

Defined in ClickHaskell

ToQueryPart Int64 Source # 
Instance details

Defined in ClickHaskell

Data Int64

Since: base-4.0.0.0

Instance details

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 #

toConstr :: Int64 -> Constr #

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

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int64 -> Int #

alignment :: Int64 -> Int #

peekElemOff :: Ptr Int64 -> Int -> IO Int64 #

pokeElemOff :: Ptr Int64 -> Int -> Int64 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int64 #

pokeByteOff :: Ptr b -> Int -> Int64 -> IO () #

peek :: Ptr Int64 -> IO Int64 #

poke :: Ptr Int64 -> Int64 -> IO () #

Bits Int64

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBits Int64

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

Bounded Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Ix Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Num Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Read Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Integral Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Real Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

toRational :: Int64 -> Rational #

Show Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int64 -> ShowS #

show :: Int64 -> String #

showList :: [Int64] -> ShowS #

PrintfArg Int64

Since: base-2.1

Instance details

Defined in Text.Printf

BitOps Int64 
Instance details

Defined in Basement.Bits

FiniteBitsOps Int64 
Instance details

Defined in Basement.Bits

Subtractive Int64 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Int64 
Instance details

Defined in Basement.Numerical.Subtractive

Methods

(-) :: Int64 -> Int64 -> Difference Int64 #

PrimMemoryComparable Int64 
Instance details

Defined in Basement.PrimType

PrimType Int64 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Int64 
Instance details

Defined in Basement.PrimType

type PrimSize Int64 = 8
NFData Int64 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int64 -> () #

Eq Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

(==) :: Int64 -> Int64 -> Bool #

(/=) :: Int64 -> Int64 -> Bool #

Ord Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

compare :: Int64 -> Int64 -> Ordering #

(<) :: Int64 -> Int64 -> Bool #

(<=) :: Int64 -> Int64 -> Bool #

(>) :: Int64 -> Int64 -> Bool #

(>=) :: Int64 -> Int64 -> Bool #

max :: Int64 -> Int64 -> Int64 #

min :: Int64 -> Int64 -> Int64 #

Hashable Int64 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int64 -> Int #

hash :: Int64 -> Int #

Unbox Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

ToChType Int64 Int Source # 
Instance details

Defined in ClickHaskell

Methods

toChType :: Int -> Int64 Source #

Lift Int64 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Int64 -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Int64 -> Code m Int64 #

Vector Vector Int64 
Instance details

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 ()

elemseq :: Vector Int64 -> Int64 -> b -> b

MVector MVector Int64 
Instance details

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 # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name Int64)] -> Column (GetColumnName (Column name Int64)) (GetColumnType (Column name Int64))

type NatNumMaxBound Int64 
Instance details

Defined in Basement.Nat

type NatNumMaxBound Int64 = 9223372036854775807
type Difference Int64 
Instance details

Defined in Basement.Numerical.Subtractive

type PrimSize Int64 
Instance details

Defined in Basement.PrimType

type PrimSize Int64 = 8
newtype Vector Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int64 = V_Int64 (Vector Int64)
newtype MVector s Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int64 = MV_Int64 (MVector s Int64)

data Int128 #

Constructors

Int128 

Instances

Instances details
IsChType Int128 Source # 
Instance details

Defined in ClickHaskell

ToQueryPart Int128 Source # 
Instance details

Defined in ClickHaskell

Data Int128 
Instance details

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 
Instance details

Defined in Data.WideWord.Int128

Bits Int128 
Instance details

Defined in Data.WideWord.Int128

FiniteBits Int128 
Instance details

Defined in Data.WideWord.Int128

Bounded Int128 
Instance details

Defined in Data.WideWord.Int128

Enum Int128 
Instance details

Defined in Data.WideWord.Int128

Generic Int128 
Instance details

Defined in Data.WideWord.Int128

Associated Types

type Rep Int128 
Instance details

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)))

Methods

from :: Int128 -> Rep Int128 x #

to :: Rep Int128 x -> Int128 #

Ix Int128 
Instance details

Defined in Data.WideWord.Int128

Num Int128 
Instance details

Defined in Data.WideWord.Int128

Read Int128 
Instance details

Defined in Data.WideWord.Int128

Integral Int128 
Instance details

Defined in Data.WideWord.Int128

Real Int128 
Instance details

Defined in Data.WideWord.Int128

Show Int128 
Instance details

Defined in Data.WideWord.Int128

Binary Int128

Since: wide-word-0.1.5.0

Instance details

Defined in Data.WideWord.Int128

Methods

put :: Int128 -> Put #

get :: Get Int128 #

putList :: [Int128] -> Put #

NFData Int128 
Instance details

Defined in Data.WideWord.Int128

Methods

rnf :: Int128 -> () #

Eq Int128 
Instance details

Defined in Data.WideWord.Int128

Methods

(==) :: Int128 -> Int128 -> Bool #

(/=) :: Int128 -> Int128 -> Bool #

Ord Int128 
Instance details

Defined in Data.WideWord.Int128

Hashable Int128 
Instance details

Defined in Data.WideWord.Int128

Methods

hashWithSalt :: Int -> Int128 -> Int #

hash :: Int128 -> Int #

Prim Int128 
Instance details

Defined in Data.WideWord.Int128

KnownSymbol name => KnownColumn (Column name Int128) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name Int128)] -> Column (GetColumnName (Column name Int128)) (GetColumnType (Column name Int128))

type Rep Int128 
Instance details

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)))

type UInt8 = Word8 Source #

ClickHouse UInt8 column type

type UInt16 = Word16 Source #

ClickHouse UInt16 column type

type UInt32 = Word32 Source #

ClickHouse UInt32 column type

type UInt64 = Word64 Source #

ClickHouse UInt64 column type

type UInt128 = Word128 Source #

ClickHouse UInt128 column type

data Word128 #

Constructors

Word128 

Instances

Instances details
IsChType UInt128 Source # 
Instance details

Defined in ClickHaskell

ToQueryPart UInt128 Source # 
Instance details

Defined in ClickHaskell

Data Word128 
Instance details

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 
Instance details

Defined in Data.WideWord.Word128

Bits Word128 
Instance details

Defined in Data.WideWord.Word128

FiniteBits Word128 
Instance details

Defined in Data.WideWord.Word128

Bounded Word128 
Instance details

Defined in Data.WideWord.Word128

Enum Word128 
Instance details

Defined in Data.WideWord.Word128

Generic Word128 
Instance details

Defined in Data.WideWord.Word128

Associated Types

type Rep Word128 
Instance details

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)))

Methods

from :: Word128 -> Rep Word128 x #

to :: Rep Word128 x -> Word128 #

Ix Word128 
Instance details

Defined in Data.WideWord.Word128

Num Word128 
Instance details

Defined in Data.WideWord.Word128

Read Word128 
Instance details

Defined in Data.WideWord.Word128

Integral Word128 
Instance details

Defined in Data.WideWord.Word128

Real Word128 
Instance details

Defined in Data.WideWord.Word128

Show Word128 
Instance details

Defined in Data.WideWord.Word128

Binary Word128

Since: wide-word-0.1.5.0

Instance details

Defined in Data.WideWord.Word128

Methods

put :: Word128 -> Put #

get :: Get Word128 #

putList :: [Word128] -> Put #

NFData Word128 
Instance details

Defined in Data.WideWord.Word128

Methods

rnf :: Word128 -> () #

Eq Word128 
Instance details

Defined in Data.WideWord.Word128

Methods

(==) :: Word128 -> Word128 -> Bool #

(/=) :: Word128 -> Word128 -> Bool #

Ord Word128 
Instance details

Defined in Data.WideWord.Word128

Hashable Word128 
Instance details

Defined in Data.WideWord.Word128

Methods

hashWithSalt :: Int -> Word128 -> Int #

hash :: Word128 -> Int #

Prim Word128 
Instance details

Defined in Data.WideWord.Word128

ToChType UInt128 UInt64 Source # 
Instance details

Defined in ClickHaskell

KnownSymbol name => KnownColumn (Column name UInt128) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name UInt128)] -> Column (GetColumnName (Column name UInt128)) (GetColumnType (Column name UInt128))

type Rep Word128 
Instance details

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)))

type Nullable = Maybe Source #

ClickHouse Nullable(T) column type (type synonym for Maybe)

data LowCardinality chType Source #

ClickHouse LowCardinality(T) column type

Instances

Instances details
FromChType chType (LowCardinality chType) Source # 
Instance details

Defined in ClickHaskell

Methods

fromChType :: chType -> LowCardinality chType Source #

IsLowCardinalitySupported chType => IsChType (LowCardinality chType) Source # 
Instance details

Defined in ClickHaskell

ToQueryPart chType => ToQueryPart (LowCardinality chType) Source # 
Instance details

Defined in ClickHaskell

IsString (LowCardinality ChString) Source # 
Instance details

Defined in ClickHaskell

(NFData chType, IsLowCardinalitySupported chType) => NFData (LowCardinality chType) Source # 
Instance details

Defined in ClickHaskell

Methods

rnf :: LowCardinality chType -> () #

(Eq chType, IsLowCardinalitySupported chType) => Eq (LowCardinality chType) Source # 
Instance details

Defined in ClickHaskell

Methods

(==) :: LowCardinality chType -> LowCardinality chType -> Bool #

(/=) :: LowCardinality chType -> LowCardinality chType -> Bool #

FromChType chType outputType => FromChType (LowCardinality chType) outputType Source # 
Instance details

Defined in ClickHaskell

Methods

fromChType :: LowCardinality chType -> outputType Source #

ToChType inputType chType => ToChType (LowCardinality inputType) chType Source # 
Instance details

Defined in ClickHaskell

Methods

toChType :: chType -> LowCardinality inputType Source #

(KnownSymbol name, IsChType (LowCardinality chType), IsLowCardinalitySupported chType) => KnownColumn (Column name (LowCardinality chType)) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

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 # 
Instance details

Defined in ClickHaskell

class IsChType chType => IsLowCardinalitySupported chType Source #

Instances

Instances details
IsLowCardinalitySupported ChString Source # 
Instance details

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 # 
Instance details

Defined in ClickHaskell

(IsLowCardinalitySupported chType, IsChType (Nullable chType)) => IsLowCardinalitySupported (Nullable chType) Source # 
Instance details

Defined in ClickHaskell

newtype UUID Source #

ClickHouse UUID column type

Constructors

MkChUUID Word128 

Instances

Instances details
IsChType UUID Source # 
Instance details

Defined in ClickHaskell

ToQueryPart UUID Source # 
Instance details

Defined in ClickHaskell

Bounded UUID Source # 
Instance details

Defined in ClickHaskell

Enum UUID Source # 
Instance details

Defined in ClickHaskell

Methods

succ :: UUID -> UUID #

pred :: UUID -> UUID #

toEnum :: Int -> UUID #

fromEnum :: UUID -> Int #

enumFrom :: UUID -> [UUID] #

enumFromThen :: UUID -> UUID -> [UUID] #

enumFromTo :: UUID -> UUID -> [UUID] #

enumFromThenTo :: UUID -> UUID -> UUID -> [UUID] #

Generic UUID Source # 
Instance details

Defined in ClickHaskell

Associated Types

type Rep UUID 
Instance details

Defined in ClickHaskell

Methods

from :: UUID -> Rep UUID x #

to :: Rep UUID x -> UUID #

Num UUID Source # 
Instance details

Defined in ClickHaskell

Methods

(+) :: UUID -> UUID -> UUID #

(-) :: UUID -> UUID -> UUID #

(*) :: UUID -> UUID -> UUID #

negate :: UUID -> UUID #

abs :: UUID -> UUID #

signum :: UUID -> UUID #

fromInteger :: Integer -> UUID #

Show UUID Source # 
Instance details

Defined in ClickHaskell

Methods

showsPrec :: Int -> UUID -> ShowS #

show :: UUID -> String #

showList :: [UUID] -> ShowS #

NFData UUID Source # 
Instance details

Defined in ClickHaskell

Methods

rnf :: UUID -> () #

Eq UUID Source # 
Instance details

Defined in ClickHaskell

Methods

(==) :: UUID -> UUID -> Bool #

(/=) :: UUID -> UUID -> Bool #

ToChType UUID Word64 Source # 
Instance details

Defined in ClickHaskell

Methods

toChType :: Word64 -> UUID Source #

FromChType UUID (Word64, Word64) Source # 
Instance details

Defined in ClickHaskell

ToChType UUID (Word64, Word64) Source # 
Instance details

Defined in ClickHaskell

Methods

toChType :: (Word64, Word64) -> UUID Source #

KnownSymbol name => KnownColumn (Column name UUID) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name UUID)] -> Column (GetColumnName (Column name UUID)) (GetColumnType (Column name UUID))

type Rep UUID Source # 
Instance details

Defined in ClickHaskell

newtype Array a Source #

ClickHouse Array column type

Constructors

MkChArray [a] 

Instances

Instances details
IsChType chType => IsChType (Array chType) Source # 
Instance details

Defined in ClickHaskell

(IsChType chType, ToQueryPart chType) => ToQueryPart (Array chType) Source # 
Instance details

Defined in ClickHaskell

Methods

toQueryPart :: Array chType -> Builder Source #

Show a => Show (Array a) Source # 
Instance details

Defined in ClickHaskell

Methods

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

show :: Array a -> String #

showList :: [Array a] -> ShowS #

NFData a => NFData (Array a) Source # 
Instance details

Defined in ClickHaskell

Methods

rnf :: Array a -> () #

Eq a => Eq (Array a) Source # 
Instance details

Defined in ClickHaskell

Methods

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

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

FromChType chType inputType => FromChType (Array chType) [inputType] Source # 
Instance details

Defined in ClickHaskell

Methods

fromChType :: Array chType -> [inputType] Source #

ToChType chType inputType => ToChType (Array chType) [inputType] Source # 
Instance details

Defined in ClickHaskell

Methods

toChType :: [inputType] -> Array chType Source #

KnownSymbol name => KnownColumn (Column name (Array ChString)) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name (Array ChString))] -> Column (GetColumnName (Column name (Array ChString))) (GetColumnType (Column name (Array ChString)))

(KnownColumn (Column name (Array chType)), Deserializable chType, TypeError ('Text "Arrays deserialization still unsupported") :: Constraint) => SerializableColumn (Column name (Array chType)) Source # 
Instance details

Defined in ClickHaskell

newtype ChString Source #

ClickHouse String column type

Constructors

MkChString ByteString 

Instances

Instances details
IsChType ChString Source # 
Instance details

Defined in ClickHaskell

IsLowCardinalitySupported ChString Source # 
Instance details

Defined in ClickHaskell

ToQueryPart ChString Source # 
Instance details

Defined in ClickHaskell

IsString ChString Source # 
Instance details

Defined in ClickHaskell

Show ChString Source # 
Instance details

Defined in ClickHaskell

NFData ChString Source # 
Instance details

Defined in ClickHaskell

Methods

rnf :: ChString -> () #

Eq ChString Source # 
Instance details

Defined in ClickHaskell

FromChType ChString Builder Source # 
Instance details

Defined in ClickHaskell

FromChType ChString ByteString Source # 
Instance details

Defined in ClickHaskell

(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 # 
Instance details

Defined in ClickHaskell

ToChType ChString Builder Source # 
Instance details

Defined in ClickHaskell

ToChType ChString ByteString Source # 
Instance details

Defined in ClickHaskell

ToChType ChString Text Source # 
Instance details

Defined in ClickHaskell

ToChType ChString String Source # 
Instance details

Defined in ClickHaskell

ToChType ChString Int Source # 
Instance details

Defined in ClickHaskell

IsString (LowCardinality ChString) Source # 
Instance details

Defined in ClickHaskell

KnownSymbol name => KnownColumn (Column name (Array ChString)) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name (Array ChString))] -> Column (GetColumnName (Column name (Array ChString))) (GetColumnType (Column name (Array ChString)))

KnownSymbol name => KnownColumn (Column name ChString) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder

renderColumnType :: Builder

mkColumn :: [GetColumnType (Column name ChString)] -> Column (GetColumnName (Column name ChString)) (GetColumnType (Column name ChString))

Protocol parts

Shared

newtype UVarInt Source #

Unsigned variable-length quantity encoding

Part of protocol implementation

Constructors

MkUVarInt Word64 

Instances

Instances details
Bits UVarInt Source # 
Instance details

Defined in ClickHaskell

Bounded UVarInt Source # 
Instance details

Defined in ClickHaskell

Enum UVarInt Source # 
Instance details

Defined in ClickHaskell

Num UVarInt Source # 
Instance details

Defined in ClickHaskell

Integral UVarInt Source # 
Instance details

Defined in ClickHaskell

Real UVarInt Source # 
Instance details

Defined in ClickHaskell

Show UVarInt Source # 
Instance details

Defined in ClickHaskell

NFData UVarInt Source # 
Instance details

Defined in ClickHaskell

Methods

rnf :: UVarInt -> () #

Eq UVarInt Source # 
Instance details

Defined in ClickHaskell

Methods

(==) :: UVarInt -> UVarInt -> Bool #

(/=) :: UVarInt -> UVarInt -> Bool #

Ord UVarInt Source # 
Instance details

Defined in ClickHaskell

data SinceRevision a (revisionNumber :: Nat) Source #

Constructors

MkSinceRevision a 
NotPresented 

Data packet

data DataPacket Source #

Instances

Instances details
Generic DataPacket Source # 
Instance details

Defined in ClickHaskell

Associated Types

type Rep DataPacket 
Instance details

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))))
type Rep DataPacket Source # 
Instance details

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))))

data BlockInfo Source #

Instances

Instances details
Generic BlockInfo Source # 
Instance details

Defined in ClickHaskell

Associated Types

type Rep BlockInfo 
Instance details

Defined in ClickHaskell

type Rep BlockInfo Source # 
Instance details

Defined in ClickHaskell

Client

data ClientPacket where Source #

Instances

Instances details
Generic ClientPacket Source # 
Instance details

Defined in ClickHaskell

Associated Types

type Rep ClientPacket 
Instance details

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)))))
type Rep ClientPacket Source # 
Instance details

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 #

Instances

Instances details
Generic HelloPacket Source # 
Instance details

Defined in ClickHaskell

Associated Types

type Rep HelloPacket 
Instance details

Defined in ClickHaskell

type Rep HelloPacket Source # 
Instance details

Defined in ClickHaskell

data Addendum Source #

Constructors

MkAddendum 

Fields

Instances

Instances details
Generic Addendum Source # 
Instance details

Defined in ClickHaskell

Associated Types

type Rep Addendum 
Instance details

Defined in ClickHaskell

Methods

from :: Addendum -> Rep Addendum x #

to :: Rep Addendum x -> Addendum #

type Rep Addendum Source # 
Instance details

Defined in ClickHaskell

Query

data QueryPacket Source #

Constructors

MkQueryPacket 

Fields

Instances

Instances details
Generic QueryPacket Source # 
Instance details

Defined in ClickHaskell

Associated Types

type Rep QueryPacket 
Instance details

Defined in ClickHaskell

type Rep QueryPacket Source # 
Instance details

Defined in ClickHaskell

data DbSettings Source #

Constructors

MkDbSettings 

data ClientInfo Source #

Constructors

MkClientInfo 

Fields

Instances

Instances details
Generic ClientInfo Source # 
Instance details

Defined in ClickHaskell

Associated Types

type Rep ClientInfo 
Instance details

Defined in ClickHaskell

type Rep ClientInfo Source # 
Instance details

Defined in ClickHaskell

Server

Hello

data HelloResponse Source #

Constructors

MkHelloResponse 

Fields

Instances

Instances details
Generic HelloResponse Source # 
Instance details

Defined in ClickHaskell

Associated Types

type Rep HelloResponse 
Instance details

Defined in ClickHaskell

type Rep HelloResponse Source # 
Instance details

Defined in ClickHaskell

data PasswordComplexityRules Source #

Instances

Instances details
Generic PasswordComplexityRules Source # 
Instance details

Defined in ClickHaskell

Associated Types

type Rep PasswordComplexityRules 
Instance details

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)))
type Rep PasswordComplexityRules Source # 
Instance details

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 #

Instances

Instances details
Generic ExceptionPacket Source # 
Instance details

Defined in ClickHaskell

Associated Types

type Rep ExceptionPacket 
Instance details

Defined in ClickHaskell

Show ExceptionPacket Source # 
Instance details

Defined in ClickHaskell

type Rep ExceptionPacket Source # 
Instance details

Defined in ClickHaskell

Progress

data ProgressPacket Source #

Constructors

MkProgressPacket 

Fields

Instances

Instances details
Generic ProgressPacket Source # 
Instance details

Defined in ClickHaskell

Associated Types

type Rep ProgressPacket 
Instance details

Defined in ClickHaskell

type Rep ProgressPacket Source # 
Instance details

Defined in ClickHaskell

ProfileInfo

data ProfileInfo Source #

Constructors

MkProfileInfo 

Fields

Instances

Instances details
Generic ProfileInfo Source # 
Instance details

Defined in ClickHaskell

Associated Types

type Rep ProfileInfo 
Instance details

Defined in ClickHaskell

type Rep ProfileInfo Source # 
Instance details

Defined in ClickHaskell

TableColumns

data TableColumns Source #

Instances

Instances details
Generic TableColumns Source # 
Instance details

Defined in ClickHaskell

Associated Types

type Rep TableColumns 
Instance details

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)))
type Rep TableColumns Source # 
Instance details

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)))