Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data ChCredential = MkChCredential {
- chLogin :: Text
- chPass :: Text
- chDatabase :: Text
- chHost :: HostName
- chPort :: ServiceName
- defaultCredentials :: ChCredential
- data Connection = MkConnection {
- sock :: Socket
- user :: ChString
- bufferSize :: Int64
- revision :: ProtocolRevision
- openNativeConnection :: HasCallStack => ChCredential -> IO Connection
- data Table (name :: Symbol) (columns :: [Type])
- data Columns (columns :: [Type])
- data Column (name :: Symbol) (chType :: Type)
- class (IsChType (GetColumnType column), KnownSymbol (GetColumnName column)) => KnownColumn column where
- renderColumnName :: Builder
- renderColumnType :: Builder
- mkColumn :: [GetColumnType column] -> Column (GetColumnName column) (GetColumnType column)
- class DeserializableColumn column where
- deserializeColumn :: ProtocolRevision -> UVarInt -> Get column
- class (HasColumns hasColumns, DeserializableColumns (Columns (GetColumns hasColumns))) => ReadableFrom hasColumns record where
- deserializeColumns :: ProtocolRevision -> UVarInt -> Get [record]
- readingColumns :: Builder
- select :: forall columns record. ReadableFrom (Columns columns) record => Connection -> ChString -> IO [record]
- selectFrom :: forall table record name columns. (table ~ Table name columns, KnownSymbol name, ReadableFrom table record) => Connection -> IO [record]
- selectFromView :: forall view record name columns parameters passedParameters. (ReadableFrom view record, KnownSymbol name, view ~ View name columns parameters, CheckParameters parameters passedParameters) => Connection -> (Parameters '[] -> Parameters passedParameters) -> IO [record]
- data View (name :: Symbol) (columns :: [Type]) (parameters :: [Type])
- parameter :: forall name chType parameters userType. (ToChType chType userType, KnownParameter (Parameter name chType)) => userType -> Parameters parameters -> Parameters (Parameter name chType ': parameters)
- data Parameter (name :: Symbol) (chType :: Type)
- streamSelect :: forall columns record a. (ReadableFrom (Columns columns) record, NFData a) => Connection -> ChString -> ([record] -> IO [a]) -> IO [a]
- streamSelectFrom :: forall table record name columns a. (table ~ Table name columns, KnownSymbol name, ReadableFrom table record, NFData a) => Connection -> ([record] -> IO [a]) -> IO [a]
- streamSelectFromView :: forall view record name columns parameters passedParameters a. (ReadableFrom view record, KnownSymbol name, view ~ View name columns parameters, NFData a, CheckParameters parameters passedParameters) => Connection -> (Parameters '[] -> Parameters passedParameters) -> ([record] -> IO [a]) -> IO [a]
- handleSelect :: forall hasColumns record a. ReadableFrom hasColumns record => Connection -> Buffer -> ([record] -> IO [a]) -> IO [a]
- class (HasColumns (Columns (GetColumns columns)), Serializable (Columns (GetColumns columns)), DeserializableColumns (Columns (GetColumns columns))) => WritableInto columns record where
- serializeRecords :: ProtocolRevision -> [record] -> Builder
- writingColumns :: Builder
- columnsCount :: UVarInt
- insertInto :: forall table record name columns. (table ~ Table name columns, WritableInto table record, KnownSymbol name) => Connection -> [record] -> IO ()
- ping :: HasCallStack => Connection -> IO ()
- class KnownSymbol (ToChTypeName chType) => IsChType chType where
- type ToChTypeName chType :: Symbol
- chTypeName :: Builder
- defaultValueOfTypeName :: chType
- class IsChType chType => ToChType chType inputType where
- toChType :: inputType -> chType
- class IsChType chType => FromChType chType outputType where
- fromChType :: chType -> outputType
- class IsChType chType => ToQueryPart chType where
- toQueryPart :: chType -> Builder
- newtype ChDateTime = MkChDateTime Word32
- newtype ChDate = MkChDate Word16
- newtype ChInt8 = MkChInt8 Int8
- newtype ChInt16 = MkChInt16 Int16
- newtype ChInt32 = MkChInt32 Int32
- newtype ChInt64 = MkChInt64 Int64
- newtype ChInt128 = MkChInt128 Int128
- newtype ChUInt8 = MkChUInt8 Word8
- newtype ChUInt16 = MkChUInt16 Word16
- newtype ChUInt32 = MkChUInt32 Word32
- newtype ChUInt64 = MkChUInt64 Word64
- newtype ChUInt128 = MkChUInt128 Word128
- newtype ChString = MkChString StrictByteString
- newtype ChUUID = MkChUUID Word128
- newtype ChArray a = MkChArray [a]
- type Nullable = Maybe
- data LowCardinality chType
- class IsChType chType => IsLowCardinalitySupported chType
- newtype UVarInt = MkUVarInt Word64
- data Word128 = Word128 {
- word128Hi64 :: !Word64
- word128Lo64 :: !Word64
- data Int128 = Int128 {
- int128Hi64 :: !Word64
- int128Lo64 :: !Word64
Connection
data ChCredential Source #
MkChCredential | |
|
data Connection Source #
MkConnection | |
|
Reading and writing
data Columns (columns :: [Type]) Source #
Instances
(Serializable (Columns columns), Serializable col) => Serializable (Columns (col ': columns)) Source # | |
Defined in ClickHaskell.NativeProtocol | |
Serializable (Columns ('[] :: [Type])) Source # | |
Defined in ClickHaskell.NativeProtocol |
data Column (name :: Symbol) (chType :: Type) Source #
Column declaration
For example:
type MyColumn = Column "myColumn" ChString
Instances
class (IsChType (GetColumnType column), KnownSymbol (GetColumnName column)) => KnownColumn column where Source #
renderColumnName :: Builder Source #
renderColumnType :: Builder Source #
mkColumn :: [GetColumnType column] -> Column (GetColumnName column) (GetColumnType column) Source #
Instances
class DeserializableColumn column where Source #
deserializeColumn :: ProtocolRevision -> UVarInt -> Get column Source #
Instances
Reading
class (HasColumns hasColumns, DeserializableColumns (Columns (GetColumns hasColumns))) => ReadableFrom hasColumns record where Source #
Nothing
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 #
Simple
select :: forall columns record. ReadableFrom (Columns columns) record => Connection -> ChString -> IO [record] Source #
selectFrom :: forall table record name columns. (table ~ Table name columns, KnownSymbol name, ReadableFrom table record) => Connection -> IO [record] Source #
selectFromView :: forall view record name columns parameters passedParameters. (ReadableFrom view record, KnownSymbol name, view ~ View name columns parameters, CheckParameters parameters passedParameters) => Connection -> (Parameters '[] -> Parameters passedParameters) -> IO [record] Source #
parameter :: forall name chType parameters userType. (ToChType chType userType, KnownParameter (Parameter name chType)) => userType -> Parameters parameters -> Parameters (Parameter name chType ': parameters) Source #
Streaming
streamSelect :: forall columns record a. (ReadableFrom (Columns columns) record, NFData a) => Connection -> ChString -> ([record] -> IO [a]) -> IO [a] Source #
streamSelectFrom :: forall table record name columns a. (table ~ Table name columns, KnownSymbol name, ReadableFrom table record, NFData a) => Connection -> ([record] -> IO [a]) -> IO [a] Source #
streamSelectFromView :: forall view record name columns parameters passedParameters a. (ReadableFrom view record, KnownSymbol name, view ~ View name columns parameters, NFData a, CheckParameters parameters passedParameters) => Connection -> (Parameters '[] -> Parameters passedParameters) -> ([record] -> IO [a]) -> IO [a] Source #
Internal
handleSelect :: forall hasColumns record a. ReadableFrom hasColumns record => Connection -> Buffer -> ([record] -> IO [a]) -> IO [a] Source #
Writing
class (HasColumns (Columns (GetColumns columns)), Serializable (Columns (GetColumns columns)), DeserializableColumns (Columns (GetColumns columns))) => WritableInto columns record where Source #
Nothing
serializeRecords :: ProtocolRevision -> [record] -> Builder Source #
default serializeRecords :: GenericWritable record (GetColumns columns) => ProtocolRevision -> [record] -> 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
ping :: HasCallStack => Connection -> IO () Source #
ClickHouse types
class KnownSymbol (ToChTypeName chType) => IsChType chType where Source #
type ToChTypeName chType :: Symbol Source #
Shows database original type name
type ToChTypeName ChString = "String" type ToChTypeName (Nullable ChUInt32) = "Nullable(UInt32)"
chTypeName :: Builder Source #
defaultValueOfTypeName :: chType Source #
Instances
class IsChType chType => ToChType chType inputType where Source #
Instances
class IsChType chType => FromChType chType outputType where Source #
fromChType :: chType -> outputType Source #
Instances
class IsChType chType => ToQueryPart chType where Source #
toQueryPart :: chType -> Builder Source #
Instances
newtype ChDateTime Source #
ClickHouse DateTime column type
Instances
Instances
ClickHouse Int8 column type
Instances
ClickHouse Int16 column type
Instances
ClickHouse Int32 column type
Instances
ClickHouse Int64 column type
Instances
ClickHouse Int128 column type
Instances
ClickHouse UInt8 column type
Instances
ClickHouse UInt16 column type
Instances
ClickHouse UInt32 column type
Instances
ClickHouse UInt64 column type
Instances
ClickHouse UInt128 column type
Instances
ClickHouse String column type
Instances
ClickHouse UUID column type
Instances
MkChArray [a] |
Instances
data LowCardinality chType Source #
ClickHouse LowCardinality(T) column type
Instances
class IsChType chType => IsLowCardinalitySupported chType Source #
Instances
IsLowCardinalitySupported ChString Source # | |
Defined in ClickHaskell.NativeProtocol | |
(IsChType chType, TypeError (((((('Text "LowCardinality(" ':<>: 'ShowType chType) ':<>: 'Text ") is unsupported") ':$$: 'Text "Use one of these types:") ':$$: 'Text " ChString") ':$$: 'Text " ChDateTime") ':$$: 'Text " Nullable(T)") :: Constraint) => IsLowCardinalitySupported chType Source # | |
Defined in ClickHaskell.NativeProtocol | |
(IsLowCardinalitySupported chType, IsChType (Nullable chType)) => IsLowCardinalitySupported (Nullable chType) Source # | |
Defined in ClickHaskell.NativeProtocol |
Unsigned variable-length quantity encoding
Part of protocol implementation
Instances
Word128 | |
|
Instances
Int128 | |
|