| Copyright | (c) 2023 Dmitry Kovalev |
|---|---|
| License | BSD-3-Clause |
| Maintainer | Dmitry Kovalev |
| Stability | Experimental |
| Safe Haskell | None |
| Language | Haskell2010 |
ClickHaskell
Description
For full documentation, visit: https://clickhaskell.dev/
Synopsis
- data ConnectionArgs
- defaultConnectionArgs :: ConnectionArgs
- setHost :: HostName -> ConnectionArgs -> ConnectionArgs
- setPort :: ServiceName -> ConnectionArgs -> ConnectionArgs
- setUser :: String -> ConnectionArgs -> ConnectionArgs
- setDatabase :: String -> ConnectionArgs -> ConnectionArgs
- setPassword :: String -> ConnectionArgs -> ConnectionArgs
- data Connection where
- MkConnection :: MVar ConnectionState -> Connection
- openConnection :: HasCallStack => ConnectionArgs -> IO Connection
- overrideInitConnection :: (HostName -> Socket -> IO BufferArgs) -> ConnectionArgs -> ConnectionArgs
- data BufferArgs = MkBufferArgs {}
- overrideHostname :: String -> ConnectionArgs -> ConnectionArgs
- overrideOsUser :: String -> ConnectionArgs -> ConnectionArgs
- overrideDefaultPort :: ServiceName -> ConnectionArgs -> ConnectionArgs
- overrideMaxRevision :: ProtocolRevision -> ConnectionArgs -> ConnectionArgs
- data ClientError where
- data ConnectionError
- data UserError
- data InternalError
- passSettings :: Statement statement => (DbSettings -> DbSettings) -> statement -> statement
- addSetting :: forall (name :: Symbol) settType. KnownSetting name settType => settType -> DbSettings -> DbSettings
- select :: forall (columns :: [Type]) output result. (HasCallStack, ClickHaskell columns output) => Select columns output -> Connection -> ([output] -> IO result) -> IO [result]
- data Select (columns :: [Type]) output
- unsafeMkSelect :: forall (columns :: [Type]) output. ([(Builder, Builder)] -> Builder) -> Select columns output
- fromGenerateRandom :: forall (columns :: [Type]) output. (UInt64, UInt64, UInt64) -> UInt64 -> Select columns output
- fromTable :: forall (name :: Symbol) (columns :: [Type]) output. KnownSymbol name => Select columns output
- fromView :: forall (name :: Symbol) (columns :: [Type]) output (params :: [Type]). KnownSymbol name => (Parameters ('[] :: [Type]) -> Parameters params) -> Select columns output
- parameter :: forall (name :: Symbol) t (params :: [Type]). KnownParameter (Parameter name t) => t -> Parameters params -> Parameters (Parameter name t ': params)
- data Parameter (name :: Symbol) chType
- data Parameters (parameters :: [Type])
- viewParameters :: forall (passedParameters :: [Type]). (Parameters ('[] :: [Type]) -> Parameters passedParameters) -> Builder
- data Insert (columns :: [Type]) output
- unsafeMkInsert :: forall (columns :: [Type]) output. ([(Builder, Builder)] -> Builder) -> Insert columns output
- insert :: forall (columns :: [Type]) record. (HasCallStack, ClickHaskell columns record) => Insert columns record -> Connection -> [record] -> IO ()
- intoTable :: forall (name :: Symbol) (columns :: [Type]) output. KnownSymbol name => Insert columns output
- class ToQueryPart chType where
- toQueryPart :: chType -> Builder
- ping :: HasCallStack => Connection -> IO ()
- command :: HasCallStack => Connection -> Command -> IO ()
- data Command
- class GenericClickHaskell record columns => ClickHaskell (columns :: [Type]) record where
- deserializeColumns :: Bool -> ProtocolRevision -> UVarInt -> Get [record]
- serializeColumns :: [record] -> ProtocolRevision -> Builder
- expectedColumns :: [(Builder, Builder)]
- columnsCount :: UVarInt
- class ToChType chType userType where
- toChType :: userType -> chType
- fromChType :: chType -> userType
- class KnownColumn column => SerializableColumn column
- data Column (name :: Symbol) chType
- class (IsChType (GetColumnType column), KnownSymbol (GetColumnName column)) => KnownColumn column
- class IsChType chType where
- chTypeName :: String
- defaultValueOfTypeName :: chType
- data DateTime (tz :: Symbol)
- data DateTime64 (precision :: Nat) (tz :: Symbol)
- data Int8
- data Int16
- data Int32
- data Int64
- data Int128 = Int128 {
- int128Hi64 :: !Word64
- int128Lo64 :: !Word64
- type UInt8 = Word8
- type UInt16 = Word16
- type UInt32 = Word32
- type UInt64 = Word64
- type UInt128 = Word128
- type UInt256 = Word256
- data Word128 = Word128 {
- word128Hi64 :: !Word64
- word128Lo64 :: !Word64
- type Nullable = Maybe
- data LowCardinality chType
- class IsChType chType => IsLowCardinalitySupported chType
- data UUID
- data Array a
- data ChString
- data Enum8 (enums :: Symbol)
- data Enum16 (enums :: Symbol)
Connection
data ConnectionArgs Source #
See defaultConnectionArgs for documentation
defaultConnectionArgs :: ConnectionArgs Source #
Default connection settings that follow clickhouse-client defaults
These defaults can be modified with setUser, setPassword, setHost, setPort, setDatabase
For TLS support, see ClickHaskell-tls package
setHost :: HostName -> ConnectionArgs -> ConnectionArgs Source #
Overrides default hostname "localhost"
setPort :: ServiceName -> ConnectionArgs -> ConnectionArgs Source #
Set a custom port instead of the default 9000 (or 9443 if TLS is used).
The default port can only be overridden by overrideNetwork.
setUser :: String -> ConnectionArgs -> ConnectionArgs Source #
Overrides default user "default"
setDatabase :: String -> ConnectionArgs -> ConnectionArgs Source #
Overrides default database "default"
setPassword :: String -> ConnectionArgs -> ConnectionArgs Source #
Overrides default password ""
data Connection where Source #
Constructors
| MkConnection :: MVar ConnectionState -> Connection |
openConnection :: HasCallStack => ConnectionArgs -> IO Connection Source #
Hacking
overrideInitConnection :: (HostName -> Socket -> IO BufferArgs) -> ConnectionArgs -> ConnectionArgs Source #
This function should be used when you want to override the default connection behaviour
Watch ClickHaskell-tls package for example
data BufferArgs Source #
Constructors
| MkBufferArgs | |
overrideHostname :: String -> ConnectionArgs -> ConnectionArgs Source #
Overrides default client hostname value which is:
- $HOSTNAME env variable value (if set)
- "" otherwise
Client hostname being displayed in ClickHouse logs
overrideOsUser :: String -> ConnectionArgs -> ConnectionArgs Source #
Overrides default os_name value which is: 1. $USER variable value (if set) 2. "" otherwise
overrideDefaultPort :: ServiceName -> ConnectionArgs -> ConnectionArgs Source #
Override the default port used when no port was set explicitly via setPort.
This does not immediately fix the connection port:
if the user has already called setPort, that value takes precedence.
Otherwise, the given port becomes the new default.
Typical use case: provide a different default for TLS connections, e.g. 9443.
Statements and commands
Exceptions
data ClientError where Source #
Constructors
| UnmatchedResult | |
Fields
| |
| DatabaseException | |
Fields
| |
| InternalError :: HasCallStack => InternalError -> ClientError | |
Instances
| Exception ClientError Source # | |
Defined in ClickHaskell Methods toException :: ClientError -> SomeException # fromException :: SomeException -> Maybe ClientError # displayException :: ClientError -> String # backtraceDesired :: ClientError -> Bool # | |
| Show ClientError Source # | |
Defined in ClickHaskell Methods showsPrec :: Int -> ClientError -> ShowS # show :: ClientError -> String # showList :: [ClientError] -> ShowS # | |
data ConnectionError Source #
Errors occured on connection operations
Constructors
| NoAdressResolved | Occurs when |
| EstablishTimeout | Occurs on |
| ServerClosedConnection | Occurs on |
Instances
| Exception ConnectionError Source # | |
Defined in ClickHaskell.Connection Methods toException :: ConnectionError -> SomeException # fromException :: SomeException -> Maybe ConnectionError # displayException :: ConnectionError -> String # backtraceDesired :: ConnectionError -> Bool # | |
| Show ConnectionError Source # | |
Defined in ClickHaskell.Connection Methods showsPrec :: Int -> ConnectionError -> ShowS # show :: ConnectionError -> String # showList :: [ConnectionError] -> ShowS # | |
Errors intended to be handled by developers
Constructors
| UnmatchedType String | Column type mismatch in data packet |
| UnmatchedColumn String | Column name mismatch in data packet |
| UnmatchedColumnsCount String | Occurs when actual columns count less or more than expected |
Instances
| Exception UserError Source # | |
Defined in ClickHaskell Methods toException :: UserError -> SomeException # fromException :: SomeException -> Maybe UserError # displayException :: UserError -> String # backtraceDesired :: UserError -> Bool # | |
| Show UserError Source # | |
data InternalError Source #
These exceptions might indicate internal bugs.
If you encounter one, please report it.
Constructors
| UnexpectedPacketType UVarInt | |
| DeserializationError String |
Instances
| Exception InternalError Source # | |
Defined in ClickHaskell.Connection Methods toException :: InternalError -> SomeException # fromException :: SomeException -> Maybe InternalError # displayException :: InternalError -> String # backtraceDesired :: InternalError -> Bool # | |
| Show InternalError Source # | |
Defined in ClickHaskell.Connection Methods showsPrec :: Int -> InternalError -> ShowS # show :: InternalError -> String # showList :: [InternalError] -> ShowS # | |
Settings
passSettings :: Statement statement => (DbSettings -> DbSettings) -> statement -> statement Source #
Wrapper for settings passing
addSetting :: forall (name :: Symbol) settType. KnownSetting name settType => settType -> DbSettings -> DbSettings Source #
SELECT
Runner
select :: forall (columns :: [Type]) output result. (HasCallStack, ClickHaskell columns output) => Select columns output -> Connection -> ([output] -> IO result) -> IO [result] Source #
Takes Select, Connection and block processing function
Returns block processing result
Statements
unsafeMkSelect :: forall (columns :: [Type]) output. ([(Builder, Builder)] -> Builder) -> Select columns output Source #
fromGenerateRandom :: forall (columns :: [Type]) output. (UInt64, UInt64, UInt64) -> UInt64 -> Select columns output Source #
fromTable :: forall (name :: Symbol) (columns :: [Type]) output. KnownSymbol name => Select columns output Source #
Type-safe wrapper for statements like
SELECT ${columns} FROM ${table}View
fromView :: forall (name :: Symbol) (columns :: [Type]) output (params :: [Type]). KnownSymbol name => (Parameters ('[] :: [Type]) -> Parameters params) -> Select columns output Source #
parameter :: forall (name :: Symbol) t (params :: [Type]). KnownParameter (Parameter name t) => t -> Parameters params -> Parameters (Parameter name t ': params) Source #
data Parameters (parameters :: [Type]) Source #
viewParameters :: forall (passedParameters :: [Type]). (Parameters ('[] :: [Type]) -> Parameters passedParameters) -> Builder Source #
>>>viewParameters (parameter @"a3" ("a3Val" :: ChString) . parameter @"a2" ("a2Val" :: ChString))"(a3='a3Val', a2='a2Val')"
INSERT
unsafeMkInsert :: forall (columns :: [Type]) output. ([(Builder, Builder)] -> Builder) -> Insert columns output Source #
insert :: forall (columns :: [Type]) record. (HasCallStack, ClickHaskell columns record) => Insert columns record -> Connection -> [record] -> IO () Source #
intoTable :: forall (name :: Symbol) (columns :: [Type]) output. KnownSymbol name => Insert columns output Source #
Modifiers
class ToQueryPart chType where Source #
Methods
toQueryPart :: chType -> Builder Source #
Instances
Ping
ping :: HasCallStack => Connection -> IO () Source #
Commands
command :: HasCallStack => Connection -> Command -> IO () Source #
Might be used for any command without data responses
For example: CREATE, TRUNCATE, KILL, SET, GRANT
Throws exception if any data was returned
Instances
| IsString Command Source # | |
Defined in ClickHaskell.Statements Methods fromString :: String -> Command # | |
Deriving
class GenericClickHaskell record columns => ClickHaskell (columns :: [Type]) record where Source #
Minimal complete definition
Nothing
Methods
deserializeColumns :: Bool -> ProtocolRevision -> UVarInt -> Get [record] Source #
default deserializeColumns :: Bool -> ProtocolRevision -> UVarInt -> Get [record] Source #
serializeColumns :: [record] -> ProtocolRevision -> Builder Source #
default serializeColumns :: [record] -> ProtocolRevision -> Builder Source #
expectedColumns :: [(Builder, Builder)] Source #
default expectedColumns :: [(Builder, Builder)] Source #
columnsCount :: UVarInt Source #
default columnsCount :: UVarInt Source #
class ToChType chType userType where Source #
Instances
class KnownColumn column => SerializableColumn column Source #
Minimal complete definition
deserializeColumn, serializeColumn
Instances
| (KnownColumn (Column name (Array chType)), Serializable chType) => SerializableColumn (Column name (Array chType)) Source # | |
Defined in ClickHaskell.Columns Methods deserializeColumn :: ProtocolRevision -> UVarInt -> (GetColumnType (Column name (Array chType)) -> a) -> Get [a] serializeColumn :: ProtocolRevision -> (a -> GetColumnType (Column name (Array chType))) -> [a] -> Builder | |
| (KnownColumn (Column name (LowCardinality chType)), Serializable chType, IsLowCardinalitySupported chType, TypeError ('Text "LowCardinality deserialization still unsupported") :: Constraint) => SerializableColumn (Column name (LowCardinality chType)) Source # | |
Defined in ClickHaskell.Columns Methods deserializeColumn :: ProtocolRevision -> UVarInt -> (GetColumnType (Column name (LowCardinality chType)) -> a) -> Get [a] serializeColumn :: ProtocolRevision -> (a -> GetColumnType (Column name (LowCardinality chType))) -> [a] -> Builder | |
| (KnownColumn (Column name (Nullable chType)), Serializable chType, IsChType chType) => SerializableColumn (Column name (Nullable chType)) Source # | |
Defined in ClickHaskell.Columns Methods deserializeColumn :: ProtocolRevision -> UVarInt -> (GetColumnType (Column name (Nullable chType)) -> a) -> Get [a] serializeColumn :: ProtocolRevision -> (a -> GetColumnType (Column name (Nullable chType))) -> [a] -> Builder | |
| (KnownColumn (Column name chType), Serializable chType, IsChType chType) => SerializableColumn (Column name chType) Source # | |
Defined in ClickHaskell.Columns Methods deserializeColumn :: ProtocolRevision -> UVarInt -> (GetColumnType (Column name chType) -> a) -> Get [a] serializeColumn :: ProtocolRevision -> (a -> GetColumnType (Column name chType)) -> [a] -> Builder | |
data Column (name :: Symbol) chType Source #
Column declaration
For example:
type MyColumn = Column "myColumn" ChString
Instances
| (KnownSymbol name, IsChType chType) => KnownColumn (Column name (Array chType)) Source # | |
Defined in ClickHaskell.Columns Methods mkHeader :: ColumnHeader toColumn :: [GetColumnType (Column name (Array chType))] -> Column (GetColumnName (Column name (Array chType))) (GetColumnType (Column name (Array chType))) fromColumn :: Column (GetColumnName (Column name (Array chType))) (GetColumnType (Column name (Array chType))) -> [GetColumnType (Column name (Array chType))] | |
| KnownSymbol name => KnownColumn (Column name ChString) Source # | |
Defined in ClickHaskell.Columns Methods mkHeader :: ColumnHeader toColumn :: [GetColumnType (Column name ChString)] -> Column (GetColumnName (Column name ChString)) (GetColumnType (Column name ChString)) fromColumn :: Column (GetColumnName (Column name ChString)) (GetColumnType (Column name ChString)) -> [GetColumnType (Column name ChString)] | |
| (KnownSymbol name, IsChType (DateTime tz)) => KnownColumn (Column name (DateTime tz)) Source # | |
Defined in ClickHaskell.Columns Methods mkHeader :: ColumnHeader toColumn :: [GetColumnType (Column name (DateTime tz))] -> Column (GetColumnName (Column name (DateTime tz))) (GetColumnType (Column name (DateTime tz))) fromColumn :: Column (GetColumnName (Column name (DateTime tz))) (GetColumnType (Column name (DateTime tz))) -> [GetColumnType (Column name (DateTime tz))] | |
| (KnownSymbol name, IsChType (DateTime64 precision tz)) => KnownColumn (Column name (DateTime64 precision tz)) Source # | |
Defined in ClickHaskell.Columns Methods mkHeader :: ColumnHeader toColumn :: [GetColumnType (Column name (DateTime64 precision tz))] -> Column (GetColumnName (Column name (DateTime64 precision tz))) (GetColumnType (Column name (DateTime64 precision tz))) fromColumn :: Column (GetColumnName (Column name (DateTime64 precision tz))) (GetColumnType (Column name (DateTime64 precision tz))) -> [GetColumnType (Column name (DateTime64 precision tz))] | |
| (KnownSymbol name, KnownSymbol enums) => KnownColumn (Column name (Enum16 enums)) Source # | |
Defined in ClickHaskell.Columns Methods mkHeader :: ColumnHeader toColumn :: [GetColumnType (Column name (Enum16 enums))] -> Column (GetColumnName (Column name (Enum16 enums))) (GetColumnType (Column name (Enum16 enums))) fromColumn :: Column (GetColumnName (Column name (Enum16 enums))) (GetColumnType (Column name (Enum16 enums))) -> [GetColumnType (Column name (Enum16 enums))] | |
| (KnownSymbol name, KnownSymbol enums) => KnownColumn (Column name (Enum8 enums)) Source # | |
Defined in ClickHaskell.Columns Methods mkHeader :: ColumnHeader toColumn :: [GetColumnType (Column name (Enum8 enums))] -> Column (GetColumnName (Column name (Enum8 enums))) (GetColumnType (Column name (Enum8 enums))) fromColumn :: Column (GetColumnName (Column name (Enum8 enums))) (GetColumnType (Column name (Enum8 enums))) -> [GetColumnType (Column name (Enum8 enums))] | |
| (KnownSymbol name, IsChType (LowCardinality chType), IsLowCardinalitySupported chType) => KnownColumn (Column name (LowCardinality chType)) Source # | |
Defined in ClickHaskell.Columns Methods mkHeader :: ColumnHeader toColumn :: [GetColumnType (Column name (LowCardinality chType))] -> Column (GetColumnName (Column name (LowCardinality chType))) (GetColumnType (Column name (LowCardinality chType))) fromColumn :: Column (GetColumnName (Column name (LowCardinality chType))) (GetColumnType (Column name (LowCardinality chType))) -> [GetColumnType (Column name (LowCardinality chType))] | |
| (KnownSymbol name, IsChType chType, IsChType (Nullable chType)) => KnownColumn (Column name (Nullable chType)) Source # | |
Defined in ClickHaskell.Columns Methods mkHeader :: ColumnHeader toColumn :: [GetColumnType (Column name (Nullable chType))] -> Column (GetColumnName (Column name (Nullable chType))) (GetColumnType (Column name (Nullable chType))) fromColumn :: Column (GetColumnName (Column name (Nullable chType))) (GetColumnType (Column name (Nullable chType))) -> [GetColumnType (Column name (Nullable chType))] | |
| KnownSymbol name => KnownColumn (Column name UInt128) Source # | |
Defined in ClickHaskell.Columns Methods mkHeader :: ColumnHeader toColumn :: [GetColumnType (Column name UInt128)] -> Column (GetColumnName (Column name UInt128)) (GetColumnType (Column name UInt128)) fromColumn :: Column (GetColumnName (Column name UInt128)) (GetColumnType (Column name UInt128)) -> [GetColumnType (Column name UInt128)] | |
| KnownSymbol name => KnownColumn (Column name UInt16) Source # | |
Defined in ClickHaskell.Columns | |
| KnownSymbol name => KnownColumn (Column name UInt256) Source # | |
Defined in ClickHaskell.Columns Methods mkHeader :: ColumnHeader toColumn :: [GetColumnType (Column name UInt256)] -> Column (GetColumnName (Column name UInt256)) (GetColumnType (Column name UInt256)) fromColumn :: Column (GetColumnName (Column name UInt256)) (GetColumnType (Column name UInt256)) -> [GetColumnType (Column name UInt256)] | |
| KnownSymbol name => KnownColumn (Column name UInt32) Source # | |
Defined in ClickHaskell.Columns | |
| KnownSymbol name => KnownColumn (Column name UInt64) Source # | |
Defined in ClickHaskell.Columns | |
| KnownSymbol name => KnownColumn (Column name UInt8) Source # | |
Defined in ClickHaskell.Columns | |
| KnownSymbol name => KnownColumn (Column name UUID) Source # | |
Defined in ClickHaskell.Columns | |
| KnownSymbol name => KnownColumn (Column name Int16) Source # | |
Defined in ClickHaskell.Columns | |
| KnownSymbol name => KnownColumn (Column name Int32) Source # | |
Defined in ClickHaskell.Columns | |
| KnownSymbol name => KnownColumn (Column name Int64) Source # | |
Defined in ClickHaskell.Columns | |
| KnownSymbol name => KnownColumn (Column name Int8) Source # | |
Defined in ClickHaskell.Columns | |
| KnownSymbol name => KnownColumn (Column name Int128) Source # | |
Defined in ClickHaskell.Columns | |
| (KnownSymbol name, IsChType Bool) => KnownColumn (Column name Bool) Source # | |
Defined in ClickHaskell.Columns | |
| (KnownColumn (Column name (Array chType)), Serializable chType) => SerializableColumn (Column name (Array chType)) Source # | |
Defined in ClickHaskell.Columns Methods deserializeColumn :: ProtocolRevision -> UVarInt -> (GetColumnType (Column name (Array chType)) -> a) -> Get [a] serializeColumn :: ProtocolRevision -> (a -> GetColumnType (Column name (Array chType))) -> [a] -> Builder | |
| (KnownColumn (Column name (LowCardinality chType)), Serializable chType, IsLowCardinalitySupported chType, TypeError ('Text "LowCardinality deserialization still unsupported") :: Constraint) => SerializableColumn (Column name (LowCardinality chType)) Source # | |
Defined in ClickHaskell.Columns Methods deserializeColumn :: ProtocolRevision -> UVarInt -> (GetColumnType (Column name (LowCardinality chType)) -> a) -> Get [a] serializeColumn :: ProtocolRevision -> (a -> GetColumnType (Column name (LowCardinality chType))) -> [a] -> Builder | |
| (KnownColumn (Column name (Nullable chType)), Serializable chType, IsChType chType) => SerializableColumn (Column name (Nullable chType)) Source # | |
Defined in ClickHaskell.Columns Methods deserializeColumn :: ProtocolRevision -> UVarInt -> (GetColumnType (Column name (Nullable chType)) -> a) -> Get [a] serializeColumn :: ProtocolRevision -> (a -> GetColumnType (Column name (Nullable chType))) -> [a] -> Builder | |
| (KnownColumn (Column name chType), Serializable chType, IsChType chType) => SerializableColumn (Column name chType) Source # | |
Defined in ClickHaskell.Columns Methods deserializeColumn :: ProtocolRevision -> UVarInt -> (GetColumnType (Column name chType) -> a) -> Get [a] serializeColumn :: ProtocolRevision -> (a -> GetColumnType (Column name chType)) -> [a] -> Builder | |
class (IsChType (GetColumnType column), KnownSymbol (GetColumnName column)) => KnownColumn column Source #
Minimal complete definition
toColumn, fromColumn
Instances
| (KnownSymbol name, IsChType chType) => KnownColumn (Column name (Array chType)) Source # | |
Defined in ClickHaskell.Columns Methods mkHeader :: ColumnHeader toColumn :: [GetColumnType (Column name (Array chType))] -> Column (GetColumnName (Column name (Array chType))) (GetColumnType (Column name (Array chType))) fromColumn :: Column (GetColumnName (Column name (Array chType))) (GetColumnType (Column name (Array chType))) -> [GetColumnType (Column name (Array chType))] | |
| KnownSymbol name => KnownColumn (Column name ChString) Source # | |
Defined in ClickHaskell.Columns Methods mkHeader :: ColumnHeader toColumn :: [GetColumnType (Column name ChString)] -> Column (GetColumnName (Column name ChString)) (GetColumnType (Column name ChString)) fromColumn :: Column (GetColumnName (Column name ChString)) (GetColumnType (Column name ChString)) -> [GetColumnType (Column name ChString)] | |
| (KnownSymbol name, IsChType (DateTime tz)) => KnownColumn (Column name (DateTime tz)) Source # | |
Defined in ClickHaskell.Columns Methods mkHeader :: ColumnHeader toColumn :: [GetColumnType (Column name (DateTime tz))] -> Column (GetColumnName (Column name (DateTime tz))) (GetColumnType (Column name (DateTime tz))) fromColumn :: Column (GetColumnName (Column name (DateTime tz))) (GetColumnType (Column name (DateTime tz))) -> [GetColumnType (Column name (DateTime tz))] | |
| (KnownSymbol name, IsChType (DateTime64 precision tz)) => KnownColumn (Column name (DateTime64 precision tz)) Source # | |
Defined in ClickHaskell.Columns Methods mkHeader :: ColumnHeader toColumn :: [GetColumnType (Column name (DateTime64 precision tz))] -> Column (GetColumnName (Column name (DateTime64 precision tz))) (GetColumnType (Column name (DateTime64 precision tz))) fromColumn :: Column (GetColumnName (Column name (DateTime64 precision tz))) (GetColumnType (Column name (DateTime64 precision tz))) -> [GetColumnType (Column name (DateTime64 precision tz))] | |
| (KnownSymbol name, KnownSymbol enums) => KnownColumn (Column name (Enum16 enums)) Source # | |
Defined in ClickHaskell.Columns Methods mkHeader :: ColumnHeader toColumn :: [GetColumnType (Column name (Enum16 enums))] -> Column (GetColumnName (Column name (Enum16 enums))) (GetColumnType (Column name (Enum16 enums))) fromColumn :: Column (GetColumnName (Column name (Enum16 enums))) (GetColumnType (Column name (Enum16 enums))) -> [GetColumnType (Column name (Enum16 enums))] | |
| (KnownSymbol name, KnownSymbol enums) => KnownColumn (Column name (Enum8 enums)) Source # | |
Defined in ClickHaskell.Columns Methods mkHeader :: ColumnHeader toColumn :: [GetColumnType (Column name (Enum8 enums))] -> Column (GetColumnName (Column name (Enum8 enums))) (GetColumnType (Column name (Enum8 enums))) fromColumn :: Column (GetColumnName (Column name (Enum8 enums))) (GetColumnType (Column name (Enum8 enums))) -> [GetColumnType (Column name (Enum8 enums))] | |
| (KnownSymbol name, IsChType (LowCardinality chType), IsLowCardinalitySupported chType) => KnownColumn (Column name (LowCardinality chType)) Source # | |
Defined in ClickHaskell.Columns Methods mkHeader :: ColumnHeader toColumn :: [GetColumnType (Column name (LowCardinality chType))] -> Column (GetColumnName (Column name (LowCardinality chType))) (GetColumnType (Column name (LowCardinality chType))) fromColumn :: Column (GetColumnName (Column name (LowCardinality chType))) (GetColumnType (Column name (LowCardinality chType))) -> [GetColumnType (Column name (LowCardinality chType))] | |
| (KnownSymbol name, IsChType chType, IsChType (Nullable chType)) => KnownColumn (Column name (Nullable chType)) Source # | |
Defined in ClickHaskell.Columns Methods mkHeader :: ColumnHeader toColumn :: [GetColumnType (Column name (Nullable chType))] -> Column (GetColumnName (Column name (Nullable chType))) (GetColumnType (Column name (Nullable chType))) fromColumn :: Column (GetColumnName (Column name (Nullable chType))) (GetColumnType (Column name (Nullable chType))) -> [GetColumnType (Column name (Nullable chType))] | |
| KnownSymbol name => KnownColumn (Column name UInt128) Source # | |
Defined in ClickHaskell.Columns Methods mkHeader :: ColumnHeader toColumn :: [GetColumnType (Column name UInt128)] -> Column (GetColumnName (Column name UInt128)) (GetColumnType (Column name UInt128)) fromColumn :: Column (GetColumnName (Column name UInt128)) (GetColumnType (Column name UInt128)) -> [GetColumnType (Column name UInt128)] | |
| KnownSymbol name => KnownColumn (Column name UInt16) Source # | |
Defined in ClickHaskell.Columns | |
| KnownSymbol name => KnownColumn (Column name UInt256) Source # | |
Defined in ClickHaskell.Columns Methods mkHeader :: ColumnHeader toColumn :: [GetColumnType (Column name UInt256)] -> Column (GetColumnName (Column name UInt256)) (GetColumnType (Column name UInt256)) fromColumn :: Column (GetColumnName (Column name UInt256)) (GetColumnType (Column name UInt256)) -> [GetColumnType (Column name UInt256)] | |
| KnownSymbol name => KnownColumn (Column name UInt32) Source # | |
Defined in ClickHaskell.Columns | |
| KnownSymbol name => KnownColumn (Column name UInt64) Source # | |
Defined in ClickHaskell.Columns | |
| KnownSymbol name => KnownColumn (Column name UInt8) Source # | |
Defined in ClickHaskell.Columns | |
| KnownSymbol name => KnownColumn (Column name UUID) Source # | |
Defined in ClickHaskell.Columns | |
| KnownSymbol name => KnownColumn (Column name Int16) Source # | |
Defined in ClickHaskell.Columns | |
| KnownSymbol name => KnownColumn (Column name Int32) Source # | |
Defined in ClickHaskell.Columns | |
| KnownSymbol name => KnownColumn (Column name Int64) Source # | |
Defined in ClickHaskell.Columns | |
| KnownSymbol name => KnownColumn (Column name Int8) Source # | |
Defined in ClickHaskell.Columns | |
| KnownSymbol name => KnownColumn (Column name Int128) Source # | |
Defined in ClickHaskell.Columns | |
| (KnownSymbol name, IsChType Bool) => KnownColumn (Column name Bool) Source # | |
Defined in ClickHaskell.Columns | |
ClickHouse types
class IsChType chType where Source #
Methods
chTypeName :: String Source #
Shows database original type name
chTypeName @ChString = "String" chTypeName @(Nullable UInt32) = "Nullable(UInt32)"
defaultValueOfTypeName :: chType Source #
Instances
data DateTime (tz :: Symbol) Source #
ClickHouse DateTime column type (parametrized with timezone)
>>>chTypeName @(DateTime "")"DateTime">>>chTypeName @(DateTime "UTC")"DateTime('UTC')"
Note: DateTime stores whole seconds only, so converting from UTCTime
will drop any sub-second precision.
>>>let myUtcTime = posixSecondsToUTCTime 0.042_042>>>toChType @(DateTime "") @UTCTime myUtcTime0
Instances
data DateTime64 (precision :: Nat) (tz :: Symbol) Source #
ClickHouse DateTime64 column type (parametrized with timezone)
>>>chTypeName @(DateTime64 3 "")"DateTime64(3)">>>chTypeName @(DateTime64 3 "UTC")"DateTime64(3, 'UTC')"
Note: conversion from UTCTime may lose sub-second precision if
the precision parameter is lower than the actual timestamp precision.
>>>let myUtcTime = posixSecondsToUTCTime 42.000_000_042>>>toChType @(DateTime64 6 "") @UTCTime myUtcTime42000000>>>toChType @(DateTime64 9 "") @UTCTime myUtcTime42000000042
Instances
| (KnownSymbol name, IsChType (DateTime64 precision tz)) => KnownColumn (Column name (DateTime64 precision tz)) Source # | |
Defined in ClickHaskell.Columns Methods mkHeader :: ColumnHeader toColumn :: [GetColumnType (Column name (DateTime64 precision tz))] -> Column (GetColumnName (Column name (DateTime64 precision tz))) (GetColumnType (Column name (DateTime64 precision tz))) fromColumn :: Column (GetColumnName (Column name (DateTime64 precision tz))) (GetColumnType (Column name (DateTime64 precision tz))) -> [GetColumnType (Column name (DateTime64 precision tz))] | |
| (KnownSymbol tz, KnownNat precision) => IsChType (DateTime64 precision tz) Source # | |
Defined in ClickHaskell.Primitive | |
| NFData (DateTime64 precision tz) Source # | |
Defined in ClickHaskell.Primitive Methods rnf :: DateTime64 precision tz -> () # | |
| Bits (DateTime64 precision tz) Source # | |
Defined in ClickHaskell.Primitive Methods (.&.) :: DateTime64 precision tz -> DateTime64 precision tz -> DateTime64 precision tz # (.|.) :: DateTime64 precision tz -> DateTime64 precision tz -> DateTime64 precision tz # xor :: DateTime64 precision tz -> DateTime64 precision tz -> DateTime64 precision tz # complement :: DateTime64 precision tz -> DateTime64 precision tz # shift :: DateTime64 precision tz -> Int -> DateTime64 precision tz # rotate :: DateTime64 precision tz -> Int -> DateTime64 precision tz # zeroBits :: DateTime64 precision tz # bit :: Int -> DateTime64 precision tz # setBit :: DateTime64 precision tz -> Int -> DateTime64 precision tz # clearBit :: DateTime64 precision tz -> Int -> DateTime64 precision tz # complementBit :: DateTime64 precision tz -> Int -> DateTime64 precision tz # testBit :: DateTime64 precision tz -> Int -> Bool # bitSizeMaybe :: DateTime64 precision tz -> Maybe Int # bitSize :: DateTime64 precision tz -> Int # isSigned :: DateTime64 precision tz -> Bool # shiftL :: DateTime64 precision tz -> Int -> DateTime64 precision tz # unsafeShiftL :: DateTime64 precision tz -> Int -> DateTime64 precision tz # shiftR :: DateTime64 precision tz -> Int -> DateTime64 precision tz # unsafeShiftR :: DateTime64 precision tz -> Int -> DateTime64 precision tz # rotateL :: DateTime64 precision tz -> Int -> DateTime64 precision tz # rotateR :: DateTime64 precision tz -> Int -> DateTime64 precision tz # popCount :: DateTime64 precision tz -> Int # | |
| Bounded (DateTime64 precision tz) Source # | |
Defined in ClickHaskell.Primitive | |
| Enum (DateTime64 precision tz) Source # | |
Defined in ClickHaskell.Primitive Methods succ :: DateTime64 precision tz -> DateTime64 precision tz # pred :: DateTime64 precision tz -> DateTime64 precision tz # toEnum :: Int -> DateTime64 precision tz # fromEnum :: DateTime64 precision tz -> Int # enumFrom :: DateTime64 precision tz -> [DateTime64 precision tz] # enumFromThen :: DateTime64 precision tz -> DateTime64 precision tz -> [DateTime64 precision tz] # enumFromTo :: DateTime64 precision tz -> DateTime64 precision tz -> [DateTime64 precision tz] # enumFromThenTo :: DateTime64 precision tz -> DateTime64 precision tz -> DateTime64 precision tz -> [DateTime64 precision tz] # | |
| Num (DateTime64 precision tz) Source # | |
Defined in ClickHaskell.Primitive Methods (+) :: DateTime64 precision tz -> DateTime64 precision tz -> DateTime64 precision tz # (-) :: DateTime64 precision tz -> DateTime64 precision tz -> DateTime64 precision tz # (*) :: DateTime64 precision tz -> DateTime64 precision tz -> DateTime64 precision tz # negate :: DateTime64 precision tz -> DateTime64 precision tz # abs :: DateTime64 precision tz -> DateTime64 precision tz # signum :: DateTime64 precision tz -> DateTime64 precision tz # fromInteger :: Integer -> DateTime64 precision tz # | |
| Integral (DateTime64 precision tz) Source # | |
Defined in ClickHaskell.Primitive Methods quot :: DateTime64 precision tz -> DateTime64 precision tz -> DateTime64 precision tz # rem :: DateTime64 precision tz -> DateTime64 precision tz -> DateTime64 precision tz # div :: DateTime64 precision tz -> DateTime64 precision tz -> DateTime64 precision tz # mod :: DateTime64 precision tz -> DateTime64 precision tz -> DateTime64 precision tz # quotRem :: DateTime64 precision tz -> DateTime64 precision tz -> (DateTime64 precision tz, DateTime64 precision tz) # divMod :: DateTime64 precision tz -> DateTime64 precision tz -> (DateTime64 precision tz, DateTime64 precision tz) # toInteger :: DateTime64 precision tz -> Integer # | |
| Real (DateTime64 precision tz) Source # | |
Defined in ClickHaskell.Primitive Methods toRational :: DateTime64 precision tz -> Rational # | |
| Show (DateTime64 precision tz) Source # | |
Defined in ClickHaskell.Primitive Methods showsPrec :: Int -> DateTime64 precision tz -> ShowS # show :: DateTime64 precision tz -> String # showList :: [DateTime64 precision tz] -> ShowS # | |
| Eq (DateTime64 precision tz) Source # | |
Defined in ClickHaskell.Primitive Methods (==) :: DateTime64 precision tz -> DateTime64 precision tz -> Bool # (/=) :: DateTime64 precision tz -> DateTime64 precision tz -> Bool # | |
| Ord (DateTime64 precision tz) Source # | |
Defined in ClickHaskell.Primitive Methods compare :: DateTime64 precision tz -> DateTime64 precision tz -> Ordering # (<) :: DateTime64 precision tz -> DateTime64 precision tz -> Bool # (<=) :: DateTime64 precision tz -> DateTime64 precision tz -> Bool # (>) :: DateTime64 precision tz -> DateTime64 precision tz -> Bool # (>=) :: DateTime64 precision tz -> DateTime64 precision tz -> Bool # max :: DateTime64 precision tz -> DateTime64 precision tz -> DateTime64 precision tz # min :: DateTime64 precision tz -> DateTime64 precision tz -> DateTime64 precision tz # | |
| ToChType (DateTime64 precision tz) Word64 Source # | |
Defined in ClickHaskell.Primitive Methods toChType :: Word64 -> DateTime64 precision tz Source # fromChType :: DateTime64 precision tz -> Word64 Source # | |
| KnownNat precision => ToChType (DateTime64 precision tz) UTCTime Source # | |
Defined in ClickHaskell.Primitive Methods toChType :: UTCTime -> DateTime64 precision tz Source # fromChType :: DateTime64 precision tz -> UTCTime Source # | |
8-bit signed integer type
Instances
16-bit signed integer type
Instances
32-bit signed integer type
Instances
64-bit signed integer type
Instances
Constructors
| Int128 | |
Fields
| |
Instances
Constructors
| Word128 | |
Fields
| |
Instances
| IsChType UInt128 Source # | |||||
Defined in ClickHaskell.Primitive | |||||
| ToQueryPart UInt128 Source # | |||||
Defined in ClickHaskell.Primitive Methods toQueryPart :: UInt128 -> Builder Source # | |||||
| Binary Word128 | Since: wide-word-0.1.5.0 | ||||
| NFData Word128 | |||||
Defined in Data.WideWord.Word128 | |||||
| Bits Word128 | |||||
Defined in Data.WideWord.Word128 Methods (.&.) :: Word128 -> Word128 -> Word128 # (.|.) :: Word128 -> Word128 -> Word128 # xor :: Word128 -> Word128 -> Word128 # complement :: Word128 -> Word128 # shift :: Word128 -> Int -> Word128 # rotate :: Word128 -> Int -> Word128 # setBit :: Word128 -> Int -> Word128 # clearBit :: Word128 -> Int -> Word128 # complementBit :: Word128 -> Int -> Word128 # testBit :: Word128 -> Int -> Bool # bitSizeMaybe :: Word128 -> Maybe Int # shiftL :: Word128 -> Int -> Word128 # unsafeShiftL :: Word128 -> Int -> Word128 # shiftR :: Word128 -> Int -> Word128 # unsafeShiftR :: Word128 -> Int -> Word128 # rotateL :: Word128 -> Int -> Word128 # | |||||
| FiniteBits Word128 | |||||
Defined in Data.WideWord.Word128 Methods finiteBitSize :: Word128 -> Int # countLeadingZeros :: Word128 -> Int # countTrailingZeros :: Word128 -> Int # | |||||
| Data Word128 | |||||
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 # | |||||
| Bounded Word128 | |||||
| Enum Word128 | |||||
| Storable Word128 | |||||
| Generic Word128 | |||||
Defined in Data.WideWord.Word128 Associated Types
| |||||
| Ix Word128 | |||||
Defined in Data.WideWord.Word128 | |||||
| Num Word128 | |||||
| Read Word128 | |||||
| Integral Word128 | |||||
Defined in Data.WideWord.Word128 | |||||
| Real Word128 | |||||
Defined in Data.WideWord.Word128 Methods toRational :: Word128 -> Rational # | |||||
| Show Word128 | |||||
| Eq Word128 | |||||
| Ord Word128 | |||||
Defined in Data.WideWord.Word128 | |||||
| Hashable Word128 | |||||
Defined in Data.WideWord.Word128 | |||||
| Prim Word128 | |||||
Defined in Data.WideWord.Word128 Methods sizeOfType# :: Proxy Word128 -> Int# # alignmentOfType# :: Proxy Word128 -> Int# # alignment# :: Word128 -> Int# # indexByteArray# :: ByteArray# -> Int# -> Word128 # readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Word128 #) # writeByteArray# :: MutableByteArray# s -> Int# -> Word128 -> State# s -> State# s # setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Word128 -> State# s -> State# s # indexOffAddr# :: Addr# -> Int# -> Word128 # readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Word128 #) # writeOffAddr# :: Addr# -> Int# -> Word128 -> State# s -> State# s # setOffAddr# :: Addr# -> Int# -> Int# -> Word128 -> State# s -> State# s # | |||||
| KnownSymbol name => KnownColumn (Column name UInt128) Source # | |||||
Defined in ClickHaskell.Columns Methods mkHeader :: ColumnHeader toColumn :: [GetColumnType (Column name UInt128)] -> Column (GetColumnName (Column name UInt128)) (GetColumnType (Column name UInt128)) fromColumn :: Column (GetColumnName (Column name UInt128)) (GetColumnType (Column name UInt128)) -> [GetColumnType (Column name UInt128)] | |||||
| type Rep Word128 | |||||
Defined in Data.WideWord.Word128 type Rep Word128 = D1 ('MetaData "Word128" "Data.WideWord.Word128" "wide-word-0.1.8.1-LhL1nFRg225G5zHyIDGp3a" '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 LowCardinality chType Source #
ClickHouse LowCardinality(T) column type
Instances
| IsLowCardinalitySupported chType => IsChType (LowCardinality chType) Source # | |
Defined in ClickHaskell.Primitive | |
| ToQueryPart chType => ToQueryPart (LowCardinality chType) Source # | |
Defined in ClickHaskell.Primitive Methods toQueryPart :: LowCardinality chType -> Builder Source # | |
| (NFData chType, IsLowCardinalitySupported chType) => NFData (LowCardinality chType) Source # | |
Defined in ClickHaskell.Primitive Methods rnf :: LowCardinality chType -> () # | |
| IsString (LowCardinality ChString) Source # | |
Defined in ClickHaskell.Primitive Methods fromString :: String -> LowCardinality ChString # | |
| (Eq chType, IsLowCardinalitySupported chType) => Eq (LowCardinality chType) Source # | |
Defined in ClickHaskell.Primitive Methods (==) :: LowCardinality chType -> LowCardinality chType -> Bool # (/=) :: LowCardinality chType -> LowCardinality chType -> Bool # | |
| ToChType inputType chType => ToChType (LowCardinality inputType) chType Source # | |
Defined in ClickHaskell.Primitive Methods toChType :: chType -> LowCardinality inputType Source # fromChType :: LowCardinality inputType -> chType Source # | |
| (KnownSymbol name, IsChType (LowCardinality chType), IsLowCardinalitySupported chType) => KnownColumn (Column name (LowCardinality chType)) Source # | |
Defined in ClickHaskell.Columns Methods mkHeader :: ColumnHeader toColumn :: [GetColumnType (Column name (LowCardinality chType))] -> Column (GetColumnName (Column name (LowCardinality chType))) (GetColumnType (Column name (LowCardinality chType))) fromColumn :: Column (GetColumnName (Column name (LowCardinality chType))) (GetColumnType (Column name (LowCardinality chType))) -> [GetColumnType (Column name (LowCardinality chType))] | |
| (KnownColumn (Column name (LowCardinality chType)), Serializable chType, IsLowCardinalitySupported chType, TypeError ('Text "LowCardinality deserialization still unsupported") :: Constraint) => SerializableColumn (Column name (LowCardinality chType)) Source # | |
Defined in ClickHaskell.Columns Methods deserializeColumn :: ProtocolRevision -> UVarInt -> (GetColumnType (Column name (LowCardinality chType)) -> a) -> Get [a] serializeColumn :: ProtocolRevision -> (a -> GetColumnType (Column name (LowCardinality chType))) -> [a] -> Builder | |
class IsChType chType => IsLowCardinalitySupported chType Source #
Instances
| IsLowCardinalitySupported ChString Source # | |
Defined in ClickHaskell.Primitive | |
| (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.Primitive | |
| (IsLowCardinalitySupported chType, IsChType (Nullable chType)) => IsLowCardinalitySupported (Nullable chType) Source # | |
Defined in ClickHaskell.Primitive | |
ClickHouse UUID column type
Instances
| IsChType UUID Source # | |
Defined in ClickHaskell.Primitive | |
| ToQueryPart UUID Source # | |
Defined in ClickHaskell.Primitive Methods toQueryPart :: UUID -> Builder Source # | |
| NFData UUID Source # | |
Defined in ClickHaskell.Primitive | |
| Bounded UUID Source # | |
| Enum UUID Source # | |
| Generic UUID Source # | |
| Num UUID Source # | |
| Show UUID Source # | |
| Eq UUID Source # | |
| ToChType UUID (Word64, Word64) Source # | |
| KnownSymbol name => KnownColumn (Column name UUID) Source # | |
Defined in ClickHaskell.Columns | |
| type Rep UUID Source # | |
Defined in ClickHaskell.Primitive | |
ClickHouse Array column type
Instances
| Foldable Array Source # | |
Defined in ClickHaskell.Primitive Methods fold :: Monoid m => Array m -> m # foldMap :: Monoid m => (a -> m) -> Array a -> m # foldMap' :: Monoid m => (a -> m) -> Array a -> m # foldr :: (a -> b -> b) -> b -> Array a -> b # foldr' :: (a -> b -> b) -> b -> Array a -> b # foldl :: (b -> a -> b) -> b -> Array a -> b # foldl' :: (b -> a -> b) -> b -> Array a -> b # foldr1 :: (a -> a -> a) -> Array a -> a # foldl1 :: (a -> a -> a) -> Array a -> a # elem :: Eq a => a -> Array a -> Bool # maximum :: Ord a => Array a -> a # minimum :: Ord a => Array a -> a # | |
| IsChType chType => IsChType (Array chType) Source # | |
Defined in ClickHaskell.Primitive | |
| (IsChType chType, ToQueryPart chType) => ToQueryPart (Array chType) Source # | |
Defined in ClickHaskell.Primitive Methods toQueryPart :: Array chType -> Builder Source # | |
| NFData a => NFData (Array a) Source # | |
Defined in ClickHaskell.Primitive | |
| Show a => Show (Array a) Source # | |
| Eq a => Eq (Array a) Source # | |
| ToChType chType inputType => ToChType (Array chType) [inputType] Source # | |
Defined in ClickHaskell.Primitive | |
| (KnownSymbol name, IsChType chType) => KnownColumn (Column name (Array chType)) Source # | |
Defined in ClickHaskell.Columns Methods mkHeader :: ColumnHeader toColumn :: [GetColumnType (Column name (Array chType))] -> Column (GetColumnName (Column name (Array chType))) (GetColumnType (Column name (Array chType))) fromColumn :: Column (GetColumnName (Column name (Array chType))) (GetColumnType (Column name (Array chType))) -> [GetColumnType (Column name (Array chType))] | |
| (KnownColumn (Column name (Array chType)), Serializable chType) => SerializableColumn (Column name (Array chType)) Source # | |
Defined in ClickHaskell.Columns Methods deserializeColumn :: ProtocolRevision -> UVarInt -> (GetColumnType (Column name (Array chType)) -> a) -> Get [a] serializeColumn :: ProtocolRevision -> (a -> GetColumnType (Column name (Array chType))) -> [a] -> Builder | |
ClickHouse String column type
Instances
| IsChType ChString Source # | |
Defined in ClickHaskell.Primitive | |
| IsLowCardinalitySupported ChString Source # | |
Defined in ClickHaskell.Primitive | |
| ToQueryPart ChString Source # | |
Defined in ClickHaskell.Primitive Methods toQueryPart :: ChString -> Builder Source # | |
| NFData ChString Source # | |
Defined in ClickHaskell.Primitive | |
| IsString ChString Source # | |
Defined in ClickHaskell.Primitive Methods fromString :: String -> ChString # | |
| Show ChString Source # | |
| Eq ChString Source # | |
| ToChType ChString Builder Source # | |
| ToChType ChString ByteString Source # | |
Defined in ClickHaskell.Primitive | |
| ToChType ChString String Source # | |
| IsString (LowCardinality ChString) Source # | |
Defined in ClickHaskell.Primitive Methods fromString :: String -> LowCardinality ChString # | |
| KnownSymbol name => KnownColumn (Column name ChString) Source # | |
Defined in ClickHaskell.Columns Methods mkHeader :: ColumnHeader toColumn :: [GetColumnType (Column name ChString)] -> Column (GetColumnName (Column name ChString)) (GetColumnType (Column name ChString)) fromColumn :: Column (GetColumnName (Column name ChString)) (GetColumnType (Column name ChString)) -> [GetColumnType (Column name ChString)] | |
data Enum8 (enums :: Symbol) Source #
Instances
| KnownSymbol enums => IsChType (Enum8 enums) Source # | |
Defined in ClickHaskell.Primitive | |
| ToQueryPart (Enum8 enums) Source # | |
Defined in ClickHaskell.Primitive Methods toQueryPart :: Enum8 enums -> Builder Source # | |
| Bits (Enum8 enums) Source # | |
Defined in ClickHaskell.Primitive Methods (.&.) :: Enum8 enums -> Enum8 enums -> Enum8 enums # (.|.) :: Enum8 enums -> Enum8 enums -> Enum8 enums # xor :: Enum8 enums -> Enum8 enums -> Enum8 enums # complement :: Enum8 enums -> Enum8 enums # shift :: Enum8 enums -> Int -> Enum8 enums # rotate :: Enum8 enums -> Int -> Enum8 enums # setBit :: Enum8 enums -> Int -> Enum8 enums # clearBit :: Enum8 enums -> Int -> Enum8 enums # complementBit :: Enum8 enums -> Int -> Enum8 enums # testBit :: Enum8 enums -> Int -> Bool # bitSizeMaybe :: Enum8 enums -> Maybe Int # bitSize :: Enum8 enums -> Int # isSigned :: Enum8 enums -> Bool # shiftL :: Enum8 enums -> Int -> Enum8 enums # unsafeShiftL :: Enum8 enums -> Int -> Enum8 enums # shiftR :: Enum8 enums -> Int -> Enum8 enums # unsafeShiftR :: Enum8 enums -> Int -> Enum8 enums # rotateL :: Enum8 enums -> Int -> Enum8 enums # | |
| Bounded (Enum8 enums) Source # | |
| Enum (Enum8 enums) Source # | |
Defined in ClickHaskell.Primitive Methods succ :: Enum8 enums -> Enum8 enums # pred :: Enum8 enums -> Enum8 enums # toEnum :: Int -> Enum8 enums # fromEnum :: Enum8 enums -> Int # enumFrom :: Enum8 enums -> [Enum8 enums] # enumFromThen :: Enum8 enums -> Enum8 enums -> [Enum8 enums] # enumFromTo :: Enum8 enums -> Enum8 enums -> [Enum8 enums] # enumFromThenTo :: Enum8 enums -> Enum8 enums -> Enum8 enums -> [Enum8 enums] # | |
| Num (Enum8 enums) Source # | |
Defined in ClickHaskell.Primitive Methods (+) :: Enum8 enums -> Enum8 enums -> Enum8 enums # (-) :: Enum8 enums -> Enum8 enums -> Enum8 enums # (*) :: Enum8 enums -> Enum8 enums -> Enum8 enums # negate :: Enum8 enums -> Enum8 enums # abs :: Enum8 enums -> Enum8 enums # signum :: Enum8 enums -> Enum8 enums # fromInteger :: Integer -> Enum8 enums # | |
| Show (Enum8 enums) Source # | |
| Eq (Enum8 enums) Source # | |
| ToChType (Enum8 enums) Int8 Source # | |
| (KnownSymbol name, KnownSymbol enums) => KnownColumn (Column name (Enum8 enums)) Source # | |
Defined in ClickHaskell.Columns Methods mkHeader :: ColumnHeader toColumn :: [GetColumnType (Column name (Enum8 enums))] -> Column (GetColumnName (Column name (Enum8 enums))) (GetColumnType (Column name (Enum8 enums))) fromColumn :: Column (GetColumnName (Column name (Enum8 enums))) (GetColumnType (Column name (Enum8 enums))) -> [GetColumnType (Column name (Enum8 enums))] | |
data Enum16 (enums :: Symbol) Source #
Instances
| KnownSymbol enums => IsChType (Enum16 enums) Source # | |
Defined in ClickHaskell.Primitive | |
| ToQueryPart (Enum16 enums) Source # | |
Defined in ClickHaskell.Primitive Methods toQueryPart :: Enum16 enums -> Builder Source # | |
| Bits (Enum16 enums) Source # | |
Defined in ClickHaskell.Primitive Methods (.&.) :: Enum16 enums -> Enum16 enums -> Enum16 enums # (.|.) :: Enum16 enums -> Enum16 enums -> Enum16 enums # xor :: Enum16 enums -> Enum16 enums -> Enum16 enums # complement :: Enum16 enums -> Enum16 enums # shift :: Enum16 enums -> Int -> Enum16 enums # rotate :: Enum16 enums -> Int -> Enum16 enums # setBit :: Enum16 enums -> Int -> Enum16 enums # clearBit :: Enum16 enums -> Int -> Enum16 enums # complementBit :: Enum16 enums -> Int -> Enum16 enums # testBit :: Enum16 enums -> Int -> Bool # bitSizeMaybe :: Enum16 enums -> Maybe Int # bitSize :: Enum16 enums -> Int # isSigned :: Enum16 enums -> Bool # shiftL :: Enum16 enums -> Int -> Enum16 enums # unsafeShiftL :: Enum16 enums -> Int -> Enum16 enums # shiftR :: Enum16 enums -> Int -> Enum16 enums # unsafeShiftR :: Enum16 enums -> Int -> Enum16 enums # rotateL :: Enum16 enums -> Int -> Enum16 enums # | |
| Bounded (Enum16 enums) Source # | |
| Enum (Enum16 enums) Source # | |
Defined in ClickHaskell.Primitive Methods succ :: Enum16 enums -> Enum16 enums # pred :: Enum16 enums -> Enum16 enums # toEnum :: Int -> Enum16 enums # fromEnum :: Enum16 enums -> Int # enumFrom :: Enum16 enums -> [Enum16 enums] # enumFromThen :: Enum16 enums -> Enum16 enums -> [Enum16 enums] # enumFromTo :: Enum16 enums -> Enum16 enums -> [Enum16 enums] # enumFromThenTo :: Enum16 enums -> Enum16 enums -> Enum16 enums -> [Enum16 enums] # | |
| Num (Enum16 enums) Source # | |
Defined in ClickHaskell.Primitive Methods (+) :: Enum16 enums -> Enum16 enums -> Enum16 enums # (-) :: Enum16 enums -> Enum16 enums -> Enum16 enums # (*) :: Enum16 enums -> Enum16 enums -> Enum16 enums # negate :: Enum16 enums -> Enum16 enums # abs :: Enum16 enums -> Enum16 enums # signum :: Enum16 enums -> Enum16 enums # fromInteger :: Integer -> Enum16 enums # | |
| Show (Enum16 enums) Source # | |
| Eq (Enum16 enums) Source # | |
| ToChType (Enum16 enums) Int16 Source # | |
| (KnownSymbol name, KnownSymbol enums) => KnownColumn (Column name (Enum16 enums)) Source # | |
Defined in ClickHaskell.Columns Methods mkHeader :: ColumnHeader toColumn :: [GetColumnType (Column name (Enum16 enums))] -> Column (GetColumnName (Column name (Enum16 enums))) (GetColumnType (Column name (Enum16 enums))) fromColumn :: Column (GetColumnName (Column name (Enum16 enums))) (GetColumnType (Column name (Enum16 enums))) -> [GetColumnType (Column name (Enum16 enums))] | |