Safe Haskell | None |
---|---|
Language | Haskell2010 |
ClickHaskell
Synopsis
- data ChCredential = MkChCredential {
- chLogin :: Text
- chPass :: Text
- chDatabase :: Text
- chHost :: HostName
- chPort :: ServiceName
- defaultCredentials :: ChCredential
- data Connection where
- MkConnection :: MVar ConnectionState -> Connection
- 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 -> Bool -> UVarInt -> Get column
- class HasColumns hasColumns => ReadableFrom hasColumns record where
- deserializeColumns :: ProtocolRevision -> UVarInt -> Get [record]
- readingColumns :: Builder
- readingColumnsAndTypes :: Builder
- select :: forall columns record result. ReadableFrom (Columns columns) record => Connection -> ChString -> ([record] -> IO result) -> IO [result]
- selectFrom :: forall table record name columns a. (table ~ Table name columns, KnownSymbol name, ReadableFrom table record) => Connection -> ([record] -> IO a) -> IO [a]
- 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]
- 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)
- data Parameters parameters
- viewParameters :: (Parameters '[] -> Parameters passedParameters) -> Builder
- generateRandom :: forall columns record result. ReadableFrom (Columns columns) record => Connection -> (UInt64, UInt64, UInt64) -> UInt64 -> ([record] -> IO result) -> IO [result]
- handleSelect :: forall hasColumns record result. ReadableFrom hasColumns record => ConnectionState -> ([record] -> IO result) -> IO [result]
- data ClientError where
- UserError :: HasCallStack => UserError -> ClientError
- InternalError :: HasCallStack => InternalError -> ClientError
- data ConnectionError
- data UserError
- = UnmatchedType String
- | UnmatchedColumn String
- | DatabaseException ExceptionPacket
- data InternalError
- = UnexpectedPacketType ServerPacketType
- | DeserializationError String
- class (HasColumns (Columns (GetColumns columns)), Serializable (Columns (GetColumns columns))) => WritableInto columns record where
- deserializeInsertHeader :: ProtocolRevision -> Get ()
- serializeRecords :: [record] -> ProtocolRevision -> 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 ToChType chType inputType where
- toChType :: inputType -> chType
- class FromChType chType outputType where
- fromChType :: chType -> outputType
- class ToQueryPart chType where
- toQueryPart :: chType -> Builder
- newtype DateTime (tz :: Symbol) = MkDateTime Word32
- data Int8
- data Int16
- data Int32
- data Int64
- type UInt8 = Word8
- type UInt16 = Word16
- type UInt32 = Word32
- type UInt64 = Word64
- type UInt128 = Word128
- type Nullable = Maybe
- data LowCardinality chType
- class IsChType chType => IsLowCardinalitySupported chType
- type ChDate = Date
- type ChDateTime = DateTime
- type ChUInt8 = UInt8
- type ChUInt16 = UInt16
- type ChUInt32 = UInt32
- type ChUInt64 = UInt64
- type ChUInt128 = UInt128
- type ChInt8 = Int8
- type ChInt16 = Int16
- type ChInt32 = Int32
- type ChInt64 = Int64
- type ChInt128 = Int128
- newtype ChString = MkChString StrictByteString
- newtype ChUUID = MkChUUID Word128
- newtype ChArray a = MkChArray [a]
- newtype UVarInt = MkUVarInt Word64
- data Word128 = Word128 {
- word128Hi64 :: !Word64
- word128Lo64 :: !Word64
- data Int128 = Int128 {
- int128Hi64 :: !Word64
- int128Lo64 :: !Word64
Connection
data ChCredential Source #
Constructors
MkChCredential | |
Fields
|
data Connection where Source #
Constructors
MkConnection :: MVar ConnectionState -> Connection |
Reading and writing
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 #
Minimal complete definition
Methods
renderColumnName :: Builder Source #
renderColumnType :: Builder Source #
mkColumn :: [GetColumnType column] -> Column (GetColumnName column) (GetColumnType column) Source #
Instances
class DeserializableColumn column where Source #
Instances
(KnownColumn (Column name (ChArray chType)), Deserializable chType, TypeError ('Text "Arrays deserialization still unsupported") :: Constraint) => DeserializableColumn (Column name (ChArray chType)) Source # | |
Defined in ClickHaskell | |
(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 # | |
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 # | |
Defined in ClickHaskell | |
(KnownColumn (Column name chType), Deserializable chType) => DeserializableColumn (Column name chType) Source # | |
Defined in ClickHaskell |
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 #
parameter :: forall name chType parameters userType. (ToChType chType userType, KnownParameter (Parameter name chType)) => userType -> Parameters parameters -> Parameters (Parameter name chType ': parameters) 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 ClientError where Source #
Constructors
UserError :: HasCallStack => UserError -> ClientError | |
InternalError :: HasCallStack => InternalError -> ClientError |
Instances
Exception ClientError Source # | |
Defined in ClickHaskell Methods toException :: ClientError -> SomeException # fromException :: SomeException -> Maybe ClientError # displayException :: ClientError -> String # | |
Show ClientError Source # | |
Defined in ClickHaskell Methods showsPrec :: Int -> ClientError -> ShowS # show :: ClientError -> String # showList :: [ClientError] -> ShowS # |
data ConnectionError Source #
Constructors
NoAdressResolved | |
EstablishTimeout |
Instances
Exception ConnectionError Source # | |
Defined in ClickHaskell Methods toException :: ConnectionError -> SomeException # | |
Show ConnectionError Source # | |
Defined in ClickHaskell Methods showsPrec :: Int -> ConnectionError -> ShowS # show :: ConnectionError -> String # showList :: [ConnectionError] -> ShowS # |
Constructors
UnmatchedType String | |
UnmatchedColumn String | |
DatabaseException ExceptionPacket |
Instances
Exception UserError Source # | |
Defined in ClickHaskell Methods toException :: UserError -> SomeException # fromException :: SomeException -> Maybe UserError # displayException :: UserError -> String # | |
Show UserError Source # | |
data InternalError Source #
You shouldn't see this exceptions. Please report a bug if it appears
Constructors
UnexpectedPacketType ServerPacketType | |
DeserializationError String |
Instances
Exception InternalError Source # | |
Defined in ClickHaskell Methods toException :: InternalError -> SomeException # fromException :: SomeException -> Maybe InternalError # displayException :: InternalError -> String # | |
Show InternalError Source # | |
Defined in ClickHaskell Methods showsPrec :: Int -> InternalError -> ShowS # show :: InternalError -> String # showList :: [InternalError] -> ShowS # |
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
ping :: HasCallStack => Connection -> IO () Source #
ClickHouse types
class KnownSymbol (ToChTypeName chType) => IsChType chType where Source #
Minimal complete definition
Associated Types
type ToChTypeName chType :: Symbol Source #
Shows database original type name
type ToChTypeName ChString = "String" type ToChTypeName (Nullable UInt32) = "Nullable(UInt32)"
Instances
class ToChType chType inputType where Source #
Instances
ToChType ChString Builder Source # | |
ToChType ChString StrictByteString Source # | |
Defined in ClickHaskell Methods toChType :: StrictByteString -> ChString Source # | |
ToChType ChString Text Source # | |
ToChType ChString String Source # | |
ToChType ChString Int Source # | |
ToChType ChUUID Word64 Source # | |
ToChType UInt128 UInt64 Source # | |
ToChType Int64 Int Source # | |
(IsChType chType, chType ~ inputType) => ToChType chType inputType Source # | |
Defined in ClickHaskell | |
ToChType ChUUID (Word64, Word64) Source # | |
ToChType (DateTime tz) Word32 Source # | |
ToChType (DateTime tz) UTCTime Source # | |
ToChType (DateTime tz) ZonedTime Source # | |
ToChType inputType chType => ToChType (LowCardinality inputType) chType Source # | |
Defined in ClickHaskell Methods toChType :: chType -> LowCardinality inputType Source # | |
ToChType chType inputType => ToChType (ChArray chType) [inputType] Source # | |
Defined in ClickHaskell | |
ToChType inputType chType => ToChType (Nullable inputType) (Nullable chType) Source # | |
class FromChType chType outputType where Source #
Methods
fromChType :: chType -> outputType Source #
Instances
FromChType ChString Builder Source # | |
Defined in ClickHaskell Methods fromChType :: ChString -> Builder Source # | |
FromChType ChString StrictByteString Source # | |
Defined in ClickHaskell Methods | |
(TypeError ('Text "ChString to Text using FromChType convertion could cause exception" ':$$: 'Text "Decode ByteString manually if you are sure it's always can be decoded or replace it with ByteString") :: Constraint) => FromChType ChString Text Source # | |
Defined in ClickHaskell Methods fromChType :: ChString -> Text Source # | |
(IsChType chType, chType ~ inputType) => FromChType chType inputType Source # | |
Defined in ClickHaskell Methods fromChType :: chType -> inputType Source # | |
FromChType chType (LowCardinality chType) Source # | |
Defined in ClickHaskell Methods fromChType :: chType -> LowCardinality chType Source # | |
FromChType ChUUID (Word64, Word64) Source # | |
Defined in ClickHaskell | |
FromChType (DateTime tz) Word32 Source # | |
Defined in ClickHaskell Methods fromChType :: DateTime tz -> Word32 Source # | |
FromChType (DateTime tz) UTCTime Source # | |
Defined in ClickHaskell Methods fromChType :: DateTime tz -> UTCTime Source # | |
FromChType chType outputType => FromChType (LowCardinality chType) outputType Source # | |
Defined in ClickHaskell Methods fromChType :: LowCardinality chType -> outputType Source # | |
FromChType chType inputType => FromChType (ChArray chType) [inputType] Source # | |
Defined in ClickHaskell Methods fromChType :: ChArray chType -> [inputType] Source # | |
FromChType chType inputType => FromChType (Nullable chType) (Nullable inputType) Source # | |
Defined in ClickHaskell Methods fromChType :: Nullable chType -> Nullable inputType Source # |
class ToQueryPart chType where Source #
Methods
toQueryPart :: chType -> Builder Source #
Instances
newtype DateTime (tz :: Symbol) Source #
ClickHouse DateTime column type (paramtrized with timezone)
>>>
chTypeName @(DateTime "")
"DateTime">>>
chTypeName @(DateTime "UTC")
"DateTime('UTC')"
Constructors
MkDateTime Word32 |
Instances
8-bit signed integer type
Instances
16-bit signed integer type
Instances
32-bit signed integer type
Instances
64-bit signed integer type
Instances
data LowCardinality chType Source #
ClickHouse LowCardinality(T) column type
Instances
class IsChType chType => IsLowCardinalitySupported chType Source #
Instances
IsLowCardinalitySupported ChString Source # | |
Defined in ClickHaskell | |
(IsChType chType, TypeError (((((('Text "LowCardinality(" ':<>: 'ShowType chType) ':<>: 'Text ") is unsupported") ':$$: 'Text "Use one of these types:") ':$$: 'Text " ChString") ':$$: 'Text " DateTime") ':$$: 'Text " Nullable(T)") :: Constraint) => IsLowCardinalitySupported chType Source # | |
Defined in ClickHaskell | |
(IsLowCardinalitySupported chType, IsChType (Nullable chType)) => IsLowCardinalitySupported (Nullable chType) Source # | |
Defined in ClickHaskell |
type ChDateTime = DateTime Source #
Deprecated: Ch prefixed types are deprecated. Use DateTime instead
ClickHouse String column type
Constructors
MkChString StrictByteString |
Instances
ClickHouse UUID column type
Instances
IsChType ChUUID Source # | |
Defined in ClickHaskell Associated Types type ToChTypeName ChUUID :: Symbol Source # | |
ToQueryPart ChUUID Source # | |
Defined in ClickHaskell Methods toQueryPart :: ChUUID -> Builder Source # | |
Bounded ChUUID Source # | |
Enum ChUUID Source # | |
Defined in ClickHaskell | |
Generic ChUUID Source # | |
Show ChUUID Source # | |
NFData ChUUID Source # | |
Defined in ClickHaskell | |
Eq ChUUID Source # | |
ToChType ChUUID Word64 Source # | |
FromChType ChUUID (Word64, Word64) Source # | |
Defined in ClickHaskell | |
ToChType ChUUID (Word64, Word64) Source # | |
KnownSymbol name => KnownColumn (Column name ChUUID) Source # | |
type ToChTypeName ChUUID Source # | |
Defined in ClickHaskell | |
type Rep ChUUID Source # | |
Defined in ClickHaskell |
Constructors
MkChArray [a] |
Instances
Unsigned variable-length quantity encoding
Part of protocol implementation
Instances
Bits UVarInt Source # | |
Defined in ClickHaskell Methods (.&.) :: UVarInt -> UVarInt -> UVarInt # (.|.) :: UVarInt -> UVarInt -> UVarInt # xor :: UVarInt -> UVarInt -> UVarInt # complement :: UVarInt -> UVarInt # shift :: UVarInt -> Int -> UVarInt # rotate :: UVarInt -> Int -> UVarInt # setBit :: UVarInt -> Int -> UVarInt # clearBit :: UVarInt -> Int -> UVarInt # complementBit :: UVarInt -> Int -> UVarInt # testBit :: UVarInt -> Int -> Bool # bitSizeMaybe :: UVarInt -> Maybe Int # shiftL :: UVarInt -> Int -> UVarInt # unsafeShiftL :: UVarInt -> Int -> UVarInt # shiftR :: UVarInt -> Int -> UVarInt # unsafeShiftR :: UVarInt -> Int -> UVarInt # rotateL :: UVarInt -> Int -> UVarInt # | |
Bounded UVarInt Source # | |
Enum UVarInt Source # | |
Num UVarInt Source # | |
Integral UVarInt Source # | |
Defined in ClickHaskell | |
Real UVarInt Source # | |
Defined in ClickHaskell Methods toRational :: UVarInt -> Rational # | |
Show UVarInt Source # | |
NFData UVarInt Source # | |
Defined in ClickHaskell | |
Eq UVarInt Source # | |
Ord UVarInt Source # | |
Constructors
Word128 | |
Fields
|
Instances
Constructors
Int128 | |
Fields
|