ClickHaskell-0.2.0: ClickHouse driver
Safe HaskellNone
LanguageHaskell2010

ClickHaskell

Synopsis

Connection

data Connection where Source #

Constructors

MkConnection :: MVar ConnectionState -> Connection 

Reading and writing

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

data Columns (columns :: [Type]) Source #

data Column (name :: Symbol) (chType :: Type) Source #

Column declaration

For example:

type MyColumn = Column "myColumn" ChString

Instances

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

Defined in ClickHaskell

Methods

deserializeColumn :: ProtocolRevision -> Bool -> UVarInt -> Get (Column name (ChArray chType)) Source #

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

Defined in ClickHaskell

Methods

deserializeColumn :: ProtocolRevision -> Bool -> UVarInt -> Get (Column name (LowCardinality chType)) Source #

(KnownColumn (Column name (Nullable chType)), Deserializable chType) => DeserializableColumn (Column name (Nullable chType)) Source # 
Instance details

Defined in ClickHaskell

Methods

deserializeColumn :: ProtocolRevision -> Bool -> UVarInt -> Get (Column name (Nullable chType)) Source #

(KnownColumn (Column name chType), Deserializable chType) => DeserializableColumn (Column name chType) Source # 
Instance details

Defined in ClickHaskell

Methods

deserializeColumn :: ProtocolRevision -> Bool -> UVarInt -> Get (Column name chType) Source #

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

mkColumn :: [GetColumnType (Column name ChUUID)] -> Column (GetColumnName (Column name ChUUID)) (GetColumnType (Column name ChUUID)) Source #

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Minimal complete definition

mkColumn

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

mkColumn :: [GetColumnType column] -> Column (GetColumnName column) (GetColumnType column) Source #

Instances

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

mkColumn :: [GetColumnType (Column name ChUUID)] -> Column (GetColumnName (Column name ChUUID)) (GetColumnType (Column name ChUUID)) Source #

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

class DeserializableColumn column where Source #

Methods

deserializeColumn :: ProtocolRevision -> Bool -> UVarInt -> Get column Source #

Instances

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

Defined in ClickHaskell

Methods

deserializeColumn :: ProtocolRevision -> Bool -> UVarInt -> Get (Column name (ChArray chType)) Source #

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

Defined in ClickHaskell

Methods

deserializeColumn :: ProtocolRevision -> Bool -> UVarInt -> Get (Column name (LowCardinality chType)) Source #

(KnownColumn (Column name (Nullable chType)), Deserializable chType) => DeserializableColumn (Column name (Nullable chType)) Source # 
Instance details

Defined in ClickHaskell

Methods

deserializeColumn :: ProtocolRevision -> Bool -> UVarInt -> Get (Column name (Nullable chType)) Source #

(KnownColumn (Column name chType), Deserializable chType) => DeserializableColumn (Column name chType) Source # 
Instance details

Defined in ClickHaskell

Methods

deserializeColumn :: ProtocolRevision -> Bool -> UVarInt -> Get (Column name chType) Source #

Reading

class HasColumns hasColumns => ReadableFrom hasColumns record where Source #

Minimal complete definition

Nothing

Methods

deserializeColumns :: ProtocolRevision -> UVarInt -> Get [record] Source #

default deserializeColumns :: GenericReadable record hasColumns => ProtocolRevision -> UVarInt -> Get [record] Source #

readingColumns :: Builder Source #

default readingColumns :: GenericReadable record hasColumns => Builder Source #

readingColumnsAndTypes :: Builder Source #

default readingColumnsAndTypes :: GenericReadable record hasColumns => Builder Source #

select :: forall columns record result. ReadableFrom (Columns columns) record => Connection -> ChString -> ([record] -> IO result) -> IO [result] Source #

selectFrom :: forall table record name columns a. (table ~ Table name columns, KnownSymbol name, ReadableFrom table record) => Connection -> ([record] -> IO a) -> IO [a] Source #

selectFromView :: forall view record result name columns parameters passedParameters. (ReadableFrom view record, KnownSymbol name, view ~ View name columns parameters, CheckParameters parameters passedParameters) => Connection -> (Parameters '[] -> Parameters passedParameters) -> ([record] -> IO result) -> IO [result] Source #

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

parameter :: forall name chType parameters userType. (ToChType chType userType, KnownParameter (Parameter name chType)) => userType -> Parameters parameters -> Parameters (Parameter name chType ': parameters) Source #

data Parameter (name :: Symbol) (chType :: Type) Source #

data Parameters parameters Source #

viewParameters :: (Parameters '[] -> Parameters passedParameters) -> Builder Source #

>>> viewParameters (parameter @"a3" @ChString ("a3Val" :: String) . parameter @"a2" @ChString ("a2Val" :: String))
"(a3='a3Val', a2='a2Val')"

generateRandom :: forall columns record result. ReadableFrom (Columns columns) record => Connection -> (UInt64, UInt64, UInt64) -> UInt64 -> ([record] -> IO result) -> IO [result] Source #

Internal

handleSelect :: forall hasColumns record result. ReadableFrom hasColumns record => ConnectionState -> ([record] -> IO result) -> IO [result] Source #

Errors

data InternalError Source #

You shouldn't see this exceptions. Please report a bug if it appears

Constructors

UnexpectedPacketType ServerPacketType 
DeserializationError String 

Writing

class (HasColumns (Columns (GetColumns columns)), Serializable (Columns (GetColumns columns))) => WritableInto columns record where Source #

Minimal complete definition

Nothing

Methods

deserializeInsertHeader :: ProtocolRevision -> Get () Source #

default deserializeInsertHeader :: GenericWritable record (GetColumns columns) => ProtocolRevision -> Get () Source #

serializeRecords :: [record] -> ProtocolRevision -> Builder Source #

default serializeRecords :: GenericWritable record (GetColumns columns) => [record] -> ProtocolRevision -> Builder Source #

writingColumns :: Builder Source #

default writingColumns :: GenericWritable record (GetColumns columns) => Builder Source #

columnsCount :: UVarInt Source #

default columnsCount :: GenericWritable record (GetColumns columns) => UVarInt Source #

insertInto :: forall table record name columns. (table ~ Table name columns, WritableInto table record, KnownSymbol name) => Connection -> [record] -> IO () Source #

Ping database connection

ClickHouse types

class KnownSymbol (ToChTypeName chType) => IsChType chType where Source #

Minimal complete definition

defaultValueOfTypeName

Associated Types

type ToChTypeName chType :: Symbol Source #

Shows database original type name

type ToChTypeName ChString = "String"
type ToChTypeName (Nullable UInt32) = "Nullable(UInt32)"

Instances

Instances details
IsChType ChString Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChString :: Symbol Source #

IsChType ChUUID Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChUUID :: Symbol Source #

IsChType UInt128 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName UInt128 :: Symbol Source #

IsChType UInt16 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName UInt16 :: Symbol Source #

IsChType UInt32 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName UInt32 :: Symbol Source #

IsChType UInt64 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName UInt64 :: Symbol Source #

IsChType UInt8 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName UInt8 :: Symbol Source #

IsChType Int16 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName Int16 :: Symbol Source #

IsChType Int32 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName Int32 :: Symbol Source #

IsChType Int64 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName Int64 :: Symbol Source #

IsChType Int8 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName Int8 :: Symbol Source #

IsChType Int128 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName Int128 :: Symbol Source #

KnownSymbol (AppendSymbol (AppendSymbol "Array(" (ToChTypeName chType)) ")") => IsChType (ChArray chType) Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName (ChArray chType) :: Symbol Source #

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

Defined in ClickHaskell

Associated Types

type ToChTypeName (DateTime tz) :: Symbol Source #

(IsLowCardinalitySupported chType, KnownSymbol (AppendSymbol (AppendSymbol "LowCardinality(" (ToChTypeName chType)) ")")) => IsChType (LowCardinality chType) Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName (LowCardinality chType) :: Symbol Source #

(IsChType chType, KnownSymbol (AppendSymbol (AppendSymbol "Nullable(" (ToChTypeName chType)) ")")) => IsChType (Nullable chType) Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName (Nullable chType) :: Symbol 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 StrictByteString 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 ChUUID Word64 Source # 
Instance details

Defined in ClickHaskell

ToChType UInt128 UInt64 Source # 
Instance details

Defined in ClickHaskell

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 ChUUID (Word64, Word64) 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

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

Defined in ClickHaskell

Methods

toChType :: chType -> LowCardinality inputType Source #

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

Defined in ClickHaskell

Methods

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

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

Defined in ClickHaskell

Methods

toChType :: Nullable chType -> Nullable inputType 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 StrictByteString 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 ChUUID (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 (ChArray chType) [inputType] Source # 
Instance details

Defined in ClickHaskell

Methods

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

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

Defined in ClickHaskell

Methods

fromChType :: Nullable chType -> Nullable inputType Source #

class ToQueryPart chType where Source #

Methods

toQueryPart :: chType -> Builder Source #

Instances

Instances details
ToQueryPart ChString Source # 
Instance details

Defined in ClickHaskell

ToQueryPart ChUUID 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 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 (ChArray chType) Source # 
Instance details

Defined in ClickHaskell

Methods

toQueryPart :: ChArray 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 #

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 (ToChTypeName (DateTime tz)) => IsChType (DateTime tz) Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName (DateTime tz) :: Symbol Source #

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 Source #

renderColumnType :: Builder Source #

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

type ToChTypeName (DateTime tz) Source # 
Instance details

Defined in ClickHaskell

type ToChTypeName (DateTime tz) = If (tz == "") "DateTime" (AppendSymbol (AppendSymbol "DateTime('" tz) "')")

data Int8 #

8-bit signed integer type

Instances

Instances details
IsChType Int8 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName Int8 :: Symbol Source #

ToQueryPart Int8 Source # 
Instance details

Defined in ClickHaskell

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 #

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 #

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 #

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

type ToChTypeName Int8 Source # 
Instance details

Defined in ClickHaskell

type ToChTypeName Int8 = "Int8"

data Int16 #

16-bit signed integer type

Instances

Instances details
IsChType Int16 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName Int16 :: Symbol Source #

ToQueryPart Int16 Source # 
Instance details

Defined in ClickHaskell

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 #

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 #

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 #

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

type ToChTypeName Int16 Source # 
Instance details

Defined in ClickHaskell

type ToChTypeName Int16 = "Int16"

data Int32 #

32-bit signed integer type

Instances

Instances details
IsChType Int32 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName Int32 :: Symbol Source #

ToQueryPart Int32 Source # 
Instance details

Defined in ClickHaskell

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 #

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 #

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 #

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

type ToChTypeName Int32 Source # 
Instance details

Defined in ClickHaskell

type ToChTypeName Int32 = "Int32"

data Int64 #

64-bit signed integer type

Instances

Instances details
IsChType Int64 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName Int64 :: Symbol Source #

ToQueryPart Int64 Source # 
Instance details

Defined in ClickHaskell

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 #

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 #

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 #

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

type ToChTypeName Int64 Source # 
Instance details

Defined in ClickHaskell

type ToChTypeName Int64 = "Int64"

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

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, KnownSymbol (AppendSymbol (AppendSymbol "LowCardinality(" (ToChTypeName chType)) ")")) => IsChType (LowCardinality chType) Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName (LowCardinality chType) :: Symbol Source #

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

Defined in ClickHaskell

IsString (LowCardinality ChString) Source # 
Instance details

Defined in ClickHaskell

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

Defined in ClickHaskell

Methods

showsPrec :: Int -> LowCardinality chType -> ShowS #

show :: LowCardinality chType -> String #

showList :: [LowCardinality chType] -> ShowS #

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

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

Defined in ClickHaskell

Methods

deserializeColumn :: ProtocolRevision -> Bool -> UVarInt -> Get (Column name (LowCardinality chType)) Source #

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

type ToChTypeName (LowCardinality chType) Source # 
Instance details

Defined in ClickHaskell

type ToChTypeName (LowCardinality chType) = AppendSymbol (AppendSymbol "LowCardinality(" (ToChTypeName chType)) ")"

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

type ChDate = Date Source #

Deprecated: Ch prefixed types are deprecated. Use Date instead

type ChDateTime = DateTime Source #

Deprecated: Ch prefixed types are deprecated. Use DateTime instead

type ChUInt8 = UInt8 Source #

Deprecated: Ch prefixed types are deprecated. Use UInt8 instead

type ChUInt16 = UInt16 Source #

Deprecated: Ch prefixed types are deprecated. Use UInt16 instead

type ChUInt32 = UInt32 Source #

Deprecated: Ch prefixed types are deprecated. Use UInt32 instead

type ChUInt64 = UInt64 Source #

Deprecated: Ch prefixed types are deprecated. Use UInt64 instead

type ChUInt128 = UInt128 Source #

Deprecated: Ch prefixed types are deprecated. Use UInt128 instead

type ChInt8 = Int8 Source #

Deprecated: Ch prefixed types are deprecated. Use Int8 instead

type ChInt16 = Int16 Source #

Deprecated: Ch prefixed types are deprecated. Use Int16 instead

type ChInt32 = Int32 Source #

Deprecated: Ch prefixed types are deprecated. Use Int32 instead

type ChInt64 = Int64 Source #

Deprecated: Ch prefixed types are deprecated. Use Int64 instead

type ChInt128 = Int128 Source #

Deprecated: Ch prefixed types are deprecated. Use Int128 instead

newtype ChString Source #

ClickHouse String column type

Instances

Instances details
IsChType ChString Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChString :: Symbol Source #

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 StrictByteString 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 StrictByteString 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 (ChArray ChString)) Source # 
Instance details

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

type ToChTypeName ChString Source # 
Instance details

Defined in ClickHaskell

type ToChTypeName ChString = "String"

newtype ChUUID Source #

ClickHouse UUID column type

Constructors

MkChUUID Word128 

Instances

Instances details
IsChType ChUUID Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChUUID :: Symbol Source #

ToQueryPart ChUUID Source # 
Instance details

Defined in ClickHaskell

Bounded ChUUID Source # 
Instance details

Defined in ClickHaskell

Enum ChUUID Source # 
Instance details

Defined in ClickHaskell

Generic ChUUID Source # 
Instance details

Defined in ClickHaskell

Associated Types

type Rep ChUUID :: Type -> Type #

Methods

from :: ChUUID -> Rep ChUUID x #

to :: Rep ChUUID x -> ChUUID #

Show ChUUID Source # 
Instance details

Defined in ClickHaskell

NFData ChUUID Source # 
Instance details

Defined in ClickHaskell

Methods

rnf :: ChUUID -> () #

Eq ChUUID Source # 
Instance details

Defined in ClickHaskell

Methods

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

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

ToChType ChUUID Word64 Source # 
Instance details

Defined in ClickHaskell

FromChType ChUUID (Word64, Word64) Source # 
Instance details

Defined in ClickHaskell

ToChType ChUUID (Word64, Word64) Source # 
Instance details

Defined in ClickHaskell

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

mkColumn :: [GetColumnType (Column name ChUUID)] -> Column (GetColumnName (Column name ChUUID)) (GetColumnType (Column name ChUUID)) Source #

type ToChTypeName ChUUID Source # 
Instance details

Defined in ClickHaskell

type ToChTypeName ChUUID = "UUID"
type Rep ChUUID Source # 
Instance details

Defined in ClickHaskell

newtype ChArray a Source #

Constructors

MkChArray [a] 

Instances

Instances details
KnownSymbol (AppendSymbol (AppendSymbol "Array(" (ToChTypeName chType)) ")") => IsChType (ChArray chType) Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName (ChArray chType) :: Symbol Source #

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

Defined in ClickHaskell

Methods

toQueryPart :: ChArray chType -> Builder Source #

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

Defined in ClickHaskell

Methods

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

show :: ChArray a -> String #

showList :: [ChArray a] -> ShowS #

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

Defined in ClickHaskell

Methods

rnf :: ChArray a -> () #

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

Defined in ClickHaskell

Methods

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

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

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

Defined in ClickHaskell

Methods

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

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

Defined in ClickHaskell

Methods

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

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

Defined in ClickHaskell

Methods

deserializeColumn :: ProtocolRevision -> Bool -> UVarInt -> Get (Column name (ChArray chType)) Source #

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

type ToChTypeName (ChArray chType) Source # 
Instance details

Defined in ClickHaskell

type ToChTypeName (ChArray chType) = AppendSymbol (AppendSymbol "Array(" (ToChTypeName chType)) ")"

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 Word128 #

Constructors

Word128 

Instances

Instances details
IsChType UInt128 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName UInt128 :: Symbol Source #

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

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 Source #

renderColumnType :: Builder Source #

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

type ToChTypeName UInt128 Source # 
Instance details

Defined in ClickHaskell

type ToChTypeName UInt128 = "UInt128"
type Rep Word128 
Instance details

Defined in Data.WideWord.Word128

type Rep Word128 = D1 ('MetaData "Word128" "Data.WideWord.Word128" "wide-word-0.1.6.0-Gy9UBPplZ5B4mxnX5SBk4B" 'False) (C1 ('MetaCons "Word128" 'PrefixI 'True) (S1 ('MetaSel ('Just "word128Hi64") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word64) :*: S1 ('MetaSel ('Just "word128Lo64") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word64)))

data Int128 #

Constructors

Int128 

Instances

Instances details
IsChType Int128 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName Int128 :: Symbol Source #

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

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 Source #

renderColumnType :: Builder Source #

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

type ToChTypeName Int128 Source # 
Instance details

Defined in ClickHaskell

type ToChTypeName Int128 = "Int128"
type Rep Int128 
Instance details

Defined in Data.WideWord.Int128

type Rep Int128 = D1 ('MetaData "Int128" "Data.WideWord.Int128" "wide-word-0.1.6.0-Gy9UBPplZ5B4mxnX5SBk4B" 'False) (C1 ('MetaCons "Int128" 'PrefixI 'True) (S1 ('MetaSel ('Just "int128Hi64") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word64) :*: S1 ('MetaSel ('Just "int128Lo64") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word64)))