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 -> UVarInt -> Get column
- class HasColumns 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)
- data Parameters parameters
- viewParameters :: (Parameters '[] -> Parameters passedParameters) -> Builder
- 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 => ConnectionState -> ([record] -> IO [a]) -> IO [a]
- 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 :: 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 ToChType chType inputType where
- toChType :: inputType -> chType
- class FromChType chType outputType where
- fromChType :: chType -> outputType
- class ToQueryPart chType where
- toQueryPart :: chType -> Builder
- newtype ChDateTime (tz :: Symbol) = 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 #
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 #
Methods
deserializeColumn :: ProtocolRevision -> UVarInt -> Get column 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 -> 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 #
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 #
data Parameters parameters Source #
viewParameters :: (Parameters '[] -> Parameters passedParameters) -> Builder Source #
>>>
parameters (parameter @"a3" @ChString ("a3Val" :: String) . parameter @"a2" @ChString ("a2Val" :: String))
"(a3='a3Val', a2='a2Val')"
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 => ConnectionState -> ([record] -> IO [a]) -> IO [a] 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 :: 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 #
Minimal complete definition
Associated Types
type ToChTypeName chType :: Symbol Source #
Shows database original type name
type ToChTypeName ChString = "String" type ToChTypeName (Nullable ChUInt32) = "Nullable(UInt32)"
Instances
class ToChType chType inputType where Source #
Instances
class FromChType chType outputType where Source #
Methods
fromChType :: chType -> outputType Source #
Instances
class ToQueryPart chType where Source #
Methods
toQueryPart :: chType -> Builder Source #
Instances
newtype ChDateTime (tz :: Symbol) Source #
ClickHouse DateTime column type (paramtrized with timezone)
>>>
chTypeName @(ChDateTime "")
"DateTime">>>
chTypeName @(ChDateTime "UTC")
"DateTime('UTC')"
Constructors
MkChDateTime Word32 |
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
Constructors
MkChInt128 Int128 |
Instances
ClickHouse UInt8 column type
Instances
ClickHouse UInt16 column type
Constructors
MkChUInt16 Word16 |
Instances
ClickHouse UInt32 column type
Constructors
MkChUInt32 Word32 |
Instances
ClickHouse UInt64 column type
Constructors
MkChUInt64 Word64 |
Instances
ClickHouse UInt128 column type
Constructors
MkChUInt128 Word128 |
Instances
ClickHouse String column type
Constructors
MkChString StrictByteString |
Instances
ClickHouse UUID column type
Instances
Constructors
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 | |
(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 | |
(IsLowCardinalitySupported chType, IsChType (Nullable chType)) => IsLowCardinalitySupported (Nullable chType) Source # | |
Defined in ClickHaskell |
Unsigned variable-length quantity encoding
Part of protocol implementation
Instances
Constructors
Word128 | |
Fields
|
Instances
Constructors
Int128 | |
Fields
|