ClickHaskell-0.2.0: ClickHouse driver
Safe HaskellNone
LanguageHaskell2010

ClickHaskell

Synopsis

Connection

data Connection where Source #

Constructors

MkConnection :: MVar ConnectionState -> Connection 

Reading and writing

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

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

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

Column declaration

For example:

type MyColumn = Column "myColumn" ChString

Instances

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

Defined in ClickHaskell

Methods

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

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

Defined in ClickHaskell

Methods

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

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

Defined in ClickHaskell

Methods

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

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

Defined in ClickHaskell

Methods

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Minimal complete definition

mkColumn

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

Instances

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

class DeserializableColumn column where Source #

Methods

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

Instances

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

Defined in ClickHaskell

Methods

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

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

Defined in ClickHaskell

Methods

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

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

Defined in ClickHaskell

Methods

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

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

Defined in ClickHaskell

Methods

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

Reading

class HasColumns hasColumns => ReadableFrom hasColumns record where Source #

Minimal complete definition

Nothing

Methods

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

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

readingColumns :: Builder Source #

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

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 #

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

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

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

data Parameters parameters Source #

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

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

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

Constructors

UnexpectedPacketType ServerPacketType 
DeserializationError String 

Writing

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

Minimal complete definition

Nothing

Methods

deserializeInsertHeader :: ProtocolRevision -> Get () Source #

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

serializeRecords :: 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

ClickHouse types

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

Minimal complete definition

defaultValueOfTypeName

Associated Types

type ToChTypeName chType :: Symbol Source #

Shows database original type name

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

Instances

Instances details
IsChType ChDate Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChDate :: Symbol Source #

IsChType ChInt128 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChInt128 :: Symbol Source #

IsChType ChInt16 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChInt16 :: Symbol Source #

IsChType ChInt32 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChInt32 :: Symbol Source #

IsChType ChInt64 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChInt64 :: Symbol Source #

IsChType ChInt8 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChInt8 :: Symbol Source #

IsChType ChString Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChString :: Symbol Source #

IsChType ChUInt128 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChUInt128 :: Symbol Source #

IsChType ChUInt16 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChUInt16 :: Symbol Source #

IsChType ChUInt32 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChUInt32 :: Symbol Source #

IsChType ChUInt64 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChUInt64 :: Symbol Source #

IsChType ChUInt8 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChUInt8 :: Symbol Source #

IsChType ChUUID Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChUUID :: Symbol Source #

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

Defined in ClickHaskell

Associated Types

type ToChTypeName (ChArray chType) :: Symbol Source #

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

Defined in ClickHaskell

Associated Types

type ToChTypeName (ChDateTime tz) :: Symbol Source #

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

Defined in ClickHaskell

Associated Types

type ToChTypeName (LowCardinality chType) :: Symbol Source #

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

Defined in ClickHaskell

Associated Types

type ToChTypeName (Nullable chType) :: Symbol Source #

class ToChType chType inputType where Source #

Methods

toChType :: inputType -> chType Source #

Instances

Instances details
ToChType ChDate Word16 Source # 
Instance details

Defined in ClickHaskell

ToChType ChInt128 Int128 Source # 
Instance details

Defined in ClickHaskell

ToChType ChInt16 Int16 Source # 
Instance details

Defined in ClickHaskell

ToChType ChInt32 Int32 Source # 
Instance details

Defined in ClickHaskell

ToChType ChInt64 Int64 Source # 
Instance details

Defined in ClickHaskell

ToChType ChInt64 Int Source # 
Instance details

Defined in ClickHaskell

Methods

toChType :: Int -> ChInt64 Source #

ToChType ChInt8 Int8 Source # 
Instance details

Defined in ClickHaskell

Methods

toChType :: Int8 -> ChInt8 Source #

ToChType ChString Builder Source # 
Instance details

Defined in ClickHaskell

ToChType ChString StrictByteString Source # 
Instance details

Defined in ClickHaskell

ToChType ChString Text Source # 
Instance details

Defined in ClickHaskell

ToChType ChString String Source # 
Instance details

Defined in ClickHaskell

ToChType ChString Int Source # 
Instance details

Defined in ClickHaskell

ToChType ChUInt128 Word64 Source # 
Instance details

Defined in ClickHaskell

ToChType ChUInt128 Word128 Source # 
Instance details

Defined in ClickHaskell

ToChType ChUInt16 Word16 Source # 
Instance details

Defined in ClickHaskell

ToChType ChUInt32 Word32 Source # 
Instance details

Defined in ClickHaskell

ToChType ChUInt64 Word64 Source # 
Instance details

Defined in ClickHaskell

ToChType ChUInt8 Word8 Source # 
Instance details

Defined in ClickHaskell

ToChType ChUUID Word64 Source # 
Instance details

Defined in ClickHaskell

(IsChType chType, chType ~ inputType) => ToChType chType inputType Source # 
Instance details

Defined in ClickHaskell

Methods

toChType :: inputType -> chType Source #

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

Defined in ClickHaskell

Methods

toChType :: LowCardinality chType -> chType Source #

ToChType ChUUID (Word64, Word64) Source # 
Instance details

Defined in ClickHaskell

ToChType (ChDateTime tz) Word32 Source # 
Instance details

Defined in ClickHaskell

ToChType (ChDateTime tz) UTCTime Source # 
Instance details

Defined in ClickHaskell

ToChType (ChDateTime tz) ZonedTime Source # 
Instance details

Defined in ClickHaskell

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

Defined in ClickHaskell

Methods

toChType :: chType -> LowCardinality chType Source #

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

Defined in ClickHaskell

Methods

toChType :: chType -> LowCardinality inputType Source #

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

Defined in ClickHaskell

Methods

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

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

Defined in ClickHaskell

Methods

toChType :: Nullable chType -> Nullable inputType Source #

class FromChType chType outputType where Source #

Methods

fromChType :: chType -> outputType Source #

Instances

Instances details
FromChType ChDate Word16 Source # 
Instance details

Defined in ClickHaskell

FromChType ChInt128 Int128 Source # 
Instance details

Defined in ClickHaskell

FromChType ChInt16 Int16 Source # 
Instance details

Defined in ClickHaskell

FromChType ChInt32 Int32 Source # 
Instance details

Defined in ClickHaskell

FromChType ChInt64 Int64 Source # 
Instance details

Defined in ClickHaskell

FromChType ChInt8 Int8 Source # 
Instance details

Defined in ClickHaskell

FromChType ChString StrictByteString Source # 
Instance details

Defined in ClickHaskell

(TypeError ('Text "ChString to Text using FromChType convertion could cause exception" ':$$: 'Text "Decode ByteString manually if you are sure it's always can be decoded or replace it with ByteString") :: Constraint) => FromChType ChString Text Source # 
Instance details

Defined in ClickHaskell

FromChType ChUInt128 Word128 Source # 
Instance details

Defined in ClickHaskell

FromChType ChUInt16 Word16 Source # 
Instance details

Defined in ClickHaskell

FromChType ChUInt32 Word32 Source # 
Instance details

Defined in ClickHaskell

FromChType ChUInt64 Word64 Source # 
Instance details

Defined in ClickHaskell

FromChType ChUInt8 Word8 Source # 
Instance details

Defined in ClickHaskell

(IsChType chType, chType ~ inputType) => FromChType chType inputType Source # 
Instance details

Defined in ClickHaskell

Methods

fromChType :: chType -> inputType Source #

IsLowCardinalitySupported chType => FromChType chType (LowCardinality chType) Source # 
Instance details

Defined in ClickHaskell

Methods

fromChType :: chType -> LowCardinality chType Source #

FromChType ChUUID (Word64, Word64) Source # 
Instance details

Defined in ClickHaskell

FromChType (ChDateTime tz) Word32 Source # 
Instance details

Defined in ClickHaskell

FromChType (ChDateTime tz) UTCTime Source # 
Instance details

Defined in ClickHaskell

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

Defined in ClickHaskell

Methods

fromChType :: LowCardinality chType -> chType Source #

(FromChType chType outputType, IsChType (LowCardinality chType), IsLowCardinalitySupported chType) => FromChType (LowCardinality chType) outputType Source # 
Instance details

Defined in ClickHaskell

Methods

fromChType :: LowCardinality chType -> outputType Source #

FromChType (ChArray chType) [chType] Source # 
Instance details

Defined in ClickHaskell

Methods

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

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

Defined in ClickHaskell

Methods

fromChType :: Nullable chType -> Nullable inputType Source #

class ToQueryPart chType where Source #

Methods

toQueryPart :: chType -> Builder Source #

Instances

Instances details
ToQueryPart ChInt128 Source # 
Instance details

Defined in ClickHaskell

ToQueryPart ChInt16 Source # 
Instance details

Defined in ClickHaskell

ToQueryPart ChInt32 Source # 
Instance details

Defined in ClickHaskell

ToQueryPart ChInt64 Source # 
Instance details

Defined in ClickHaskell

ToQueryPart ChInt8 Source # 
Instance details

Defined in ClickHaskell

ToQueryPart ChString Source # 
Instance details

Defined in ClickHaskell

ToQueryPart ChUInt128 Source # 
Instance details

Defined in ClickHaskell

ToQueryPart ChUInt16 Source # 
Instance details

Defined in ClickHaskell

ToQueryPart ChUInt32 Source # 
Instance details

Defined in ClickHaskell

ToQueryPart ChUInt64 Source # 
Instance details

Defined in ClickHaskell

ToQueryPart ChUInt8 Source # 
Instance details

Defined in ClickHaskell

ToQueryPart ChUUID Source # 
Instance details

Defined in ClickHaskell

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

Defined in ClickHaskell

Methods

toQueryPart :: ChArray chType -> Builder Source #

IsChType (ChDateTime tz) => ToQueryPart (ChDateTime tz) Source # 
Instance details

Defined in ClickHaskell

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

Defined in ClickHaskell

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

Defined in ClickHaskell

Methods

toQueryPart :: Nullable chType -> Builder Source #

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

Defined in ClickHaskell

Associated Types

type ToChTypeName (ChDateTime tz) :: Symbol Source #

IsChType (ChDateTime tz) => ToQueryPart (ChDateTime tz) Source # 
Instance details

Defined in ClickHaskell

Bits (ChDateTime tz) Source # 
Instance details

Defined in ClickHaskell

Bounded (ChDateTime tz) Source # 
Instance details

Defined in ClickHaskell

Enum (ChDateTime tz) Source # 
Instance details

Defined in ClickHaskell

Num (ChDateTime tz) Source # 
Instance details

Defined in ClickHaskell

Integral (ChDateTime tz) Source # 
Instance details

Defined in ClickHaskell

Real (ChDateTime tz) Source # 
Instance details

Defined in ClickHaskell

Show (ChDateTime tz) Source # 
Instance details

Defined in ClickHaskell

Methods

showsPrec :: Int -> ChDateTime tz -> ShowS #

show :: ChDateTime tz -> String #

showList :: [ChDateTime tz] -> ShowS #

NFData (ChDateTime tz) Source # 
Instance details

Defined in ClickHaskell

Methods

rnf :: ChDateTime tz -> () #

Eq (ChDateTime tz) Source # 
Instance details

Defined in ClickHaskell

Methods

(==) :: ChDateTime tz -> ChDateTime tz -> Bool #

(/=) :: ChDateTime tz -> ChDateTime tz -> Bool #

Ord (ChDateTime tz) Source # 
Instance details

Defined in ClickHaskell

Methods

compare :: ChDateTime tz -> ChDateTime tz -> Ordering #

(<) :: ChDateTime tz -> ChDateTime tz -> Bool #

(<=) :: ChDateTime tz -> ChDateTime tz -> Bool #

(>) :: ChDateTime tz -> ChDateTime tz -> Bool #

(>=) :: ChDateTime tz -> ChDateTime tz -> Bool #

max :: ChDateTime tz -> ChDateTime tz -> ChDateTime tz #

min :: ChDateTime tz -> ChDateTime tz -> ChDateTime tz #

Prim (ChDateTime tz) Source # 
Instance details

Defined in ClickHaskell

FromChType (ChDateTime tz) Word32 Source # 
Instance details

Defined in ClickHaskell

FromChType (ChDateTime tz) UTCTime Source # 
Instance details

Defined in ClickHaskell

ToChType (ChDateTime tz) Word32 Source # 
Instance details

Defined in ClickHaskell

ToChType (ChDateTime tz) UTCTime Source # 
Instance details

Defined in ClickHaskell

ToChType (ChDateTime tz) ZonedTime Source # 
Instance details

Defined in ClickHaskell

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

type ToChTypeName (ChDateTime tz) Source # 
Instance details

Defined in ClickHaskell

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

newtype ChDate Source #

Constructors

MkChDate Word16 

Instances

Instances details
IsChType ChDate Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChDate :: Symbol Source #

Bits ChDate Source # 
Instance details

Defined in ClickHaskell

Bounded ChDate Source # 
Instance details

Defined in ClickHaskell

Enum ChDate Source # 
Instance details

Defined in ClickHaskell

Show ChDate Source # 
Instance details

Defined in ClickHaskell

NFData ChDate Source # 
Instance details

Defined in ClickHaskell

Methods

rnf :: ChDate -> () #

Eq ChDate Source # 
Instance details

Defined in ClickHaskell

Methods

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

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

Prim ChDate Source # 
Instance details

Defined in ClickHaskell

FromChType ChDate Word16 Source # 
Instance details

Defined in ClickHaskell

ToChType ChDate Word16 Source # 
Instance details

Defined in ClickHaskell

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

type ToChTypeName ChDate Source # 
Instance details

Defined in ClickHaskell

type ToChTypeName ChDate = "Date"

newtype ChInt8 Source #

ClickHouse Int8 column type

Constructors

MkChInt8 Int8 

Instances

Instances details
IsChType ChInt8 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChInt8 :: Symbol Source #

ToQueryPart ChInt8 Source # 
Instance details

Defined in ClickHaskell

Bits ChInt8 Source # 
Instance details

Defined in ClickHaskell

Bounded ChInt8 Source # 
Instance details

Defined in ClickHaskell

Enum ChInt8 Source # 
Instance details

Defined in ClickHaskell

Num ChInt8 Source # 
Instance details

Defined in ClickHaskell

Integral ChInt8 Source # 
Instance details

Defined in ClickHaskell

Real ChInt8 Source # 
Instance details

Defined in ClickHaskell

Show ChInt8 Source # 
Instance details

Defined in ClickHaskell

NFData ChInt8 Source # 
Instance details

Defined in ClickHaskell

Methods

rnf :: ChInt8 -> () #

Eq ChInt8 Source # 
Instance details

Defined in ClickHaskell

Methods

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

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

Ord ChInt8 Source # 
Instance details

Defined in ClickHaskell

Prim ChInt8 Source # 
Instance details

Defined in ClickHaskell

FromChType ChInt8 Int8 Source # 
Instance details

Defined in ClickHaskell

ToChType ChInt8 Int8 Source # 
Instance details

Defined in ClickHaskell

Methods

toChType :: Int8 -> ChInt8 Source #

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

type ToChTypeName ChInt8 Source # 
Instance details

Defined in ClickHaskell

type ToChTypeName ChInt8 = "Int8"

newtype ChInt16 Source #

ClickHouse Int16 column type

Constructors

MkChInt16 Int16 

Instances

Instances details
IsChType ChInt16 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChInt16 :: Symbol Source #

ToQueryPart ChInt16 Source # 
Instance details

Defined in ClickHaskell

Bits ChInt16 Source # 
Instance details

Defined in ClickHaskell

Bounded ChInt16 Source # 
Instance details

Defined in ClickHaskell

Enum ChInt16 Source # 
Instance details

Defined in ClickHaskell

Num ChInt16 Source # 
Instance details

Defined in ClickHaskell

Integral ChInt16 Source # 
Instance details

Defined in ClickHaskell

Real ChInt16 Source # 
Instance details

Defined in ClickHaskell

Show ChInt16 Source # 
Instance details

Defined in ClickHaskell

NFData ChInt16 Source # 
Instance details

Defined in ClickHaskell

Methods

rnf :: ChInt16 -> () #

Eq ChInt16 Source # 
Instance details

Defined in ClickHaskell

Methods

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

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

Ord ChInt16 Source # 
Instance details

Defined in ClickHaskell

Prim ChInt16 Source # 
Instance details

Defined in ClickHaskell

FromChType ChInt16 Int16 Source # 
Instance details

Defined in ClickHaskell

ToChType ChInt16 Int16 Source # 
Instance details

Defined in ClickHaskell

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

type ToChTypeName ChInt16 Source # 
Instance details

Defined in ClickHaskell

type ToChTypeName ChInt16 = "Int16"

newtype ChInt32 Source #

ClickHouse Int32 column type

Constructors

MkChInt32 Int32 

Instances

Instances details
IsChType ChInt32 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChInt32 :: Symbol Source #

ToQueryPart ChInt32 Source # 
Instance details

Defined in ClickHaskell

Bits ChInt32 Source # 
Instance details

Defined in ClickHaskell

Bounded ChInt32 Source # 
Instance details

Defined in ClickHaskell

Enum ChInt32 Source # 
Instance details

Defined in ClickHaskell

Num ChInt32 Source # 
Instance details

Defined in ClickHaskell

Integral ChInt32 Source # 
Instance details

Defined in ClickHaskell

Real ChInt32 Source # 
Instance details

Defined in ClickHaskell

Show ChInt32 Source # 
Instance details

Defined in ClickHaskell

NFData ChInt32 Source # 
Instance details

Defined in ClickHaskell

Methods

rnf :: ChInt32 -> () #

Eq ChInt32 Source # 
Instance details

Defined in ClickHaskell

Methods

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

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

Ord ChInt32 Source # 
Instance details

Defined in ClickHaskell

Prim ChInt32 Source # 
Instance details

Defined in ClickHaskell

FromChType ChInt32 Int32 Source # 
Instance details

Defined in ClickHaskell

ToChType ChInt32 Int32 Source # 
Instance details

Defined in ClickHaskell

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

type ToChTypeName ChInt32 Source # 
Instance details

Defined in ClickHaskell

type ToChTypeName ChInt32 = "Int32"

newtype ChInt64 Source #

ClickHouse Int64 column type

Constructors

MkChInt64 Int64 

Instances

Instances details
IsChType ChInt64 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChInt64 :: Symbol Source #

ToQueryPart ChInt64 Source # 
Instance details

Defined in ClickHaskell

Bits ChInt64 Source # 
Instance details

Defined in ClickHaskell

Bounded ChInt64 Source # 
Instance details

Defined in ClickHaskell

Enum ChInt64 Source # 
Instance details

Defined in ClickHaskell

Num ChInt64 Source # 
Instance details

Defined in ClickHaskell

Integral ChInt64 Source # 
Instance details

Defined in ClickHaskell

Real ChInt64 Source # 
Instance details

Defined in ClickHaskell

Show ChInt64 Source # 
Instance details

Defined in ClickHaskell

NFData ChInt64 Source # 
Instance details

Defined in ClickHaskell

Methods

rnf :: ChInt64 -> () #

Eq ChInt64 Source # 
Instance details

Defined in ClickHaskell

Methods

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

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

Ord ChInt64 Source # 
Instance details

Defined in ClickHaskell

Prim ChInt64 Source # 
Instance details

Defined in ClickHaskell

FromChType ChInt64 Int64 Source # 
Instance details

Defined in ClickHaskell

ToChType ChInt64 Int64 Source # 
Instance details

Defined in ClickHaskell

ToChType ChInt64 Int Source # 
Instance details

Defined in ClickHaskell

Methods

toChType :: Int -> ChInt64 Source #

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

type ToChTypeName ChInt64 Source # 
Instance details

Defined in ClickHaskell

type ToChTypeName ChInt64 = "Int64"

newtype ChInt128 Source #

ClickHouse Int128 column type

Constructors

MkChInt128 Int128 

Instances

Instances details
IsChType ChInt128 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChInt128 :: Symbol Source #

ToQueryPart ChInt128 Source # 
Instance details

Defined in ClickHaskell

Bits ChInt128 Source # 
Instance details

Defined in ClickHaskell

Bounded ChInt128 Source # 
Instance details

Defined in ClickHaskell

Enum ChInt128 Source # 
Instance details

Defined in ClickHaskell

Num ChInt128 Source # 
Instance details

Defined in ClickHaskell

Integral ChInt128 Source # 
Instance details

Defined in ClickHaskell

Real ChInt128 Source # 
Instance details

Defined in ClickHaskell

Show ChInt128 Source # 
Instance details

Defined in ClickHaskell

NFData ChInt128 Source # 
Instance details

Defined in ClickHaskell

Methods

rnf :: ChInt128 -> () #

Eq ChInt128 Source # 
Instance details

Defined in ClickHaskell

Ord ChInt128 Source # 
Instance details

Defined in ClickHaskell

Prim ChInt128 Source # 
Instance details

Defined in ClickHaskell

FromChType ChInt128 Int128 Source # 
Instance details

Defined in ClickHaskell

ToChType ChInt128 Int128 Source # 
Instance details

Defined in ClickHaskell

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

type ToChTypeName ChInt128 Source # 
Instance details

Defined in ClickHaskell

type ToChTypeName ChInt128 = "Int128"

newtype ChUInt8 Source #

ClickHouse UInt8 column type

Constructors

MkChUInt8 Word8 

Instances

Instances details
IsChType ChUInt8 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChUInt8 :: Symbol Source #

ToQueryPart ChUInt8 Source # 
Instance details

Defined in ClickHaskell

Bits ChUInt8 Source # 
Instance details

Defined in ClickHaskell

Bounded ChUInt8 Source # 
Instance details

Defined in ClickHaskell

Enum ChUInt8 Source # 
Instance details

Defined in ClickHaskell

Num ChUInt8 Source # 
Instance details

Defined in ClickHaskell

Integral ChUInt8 Source # 
Instance details

Defined in ClickHaskell

Real ChUInt8 Source # 
Instance details

Defined in ClickHaskell

Show ChUInt8 Source # 
Instance details

Defined in ClickHaskell

NFData ChUInt8 Source # 
Instance details

Defined in ClickHaskell

Methods

rnf :: ChUInt8 -> () #

Eq ChUInt8 Source # 
Instance details

Defined in ClickHaskell

Methods

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

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

Ord ChUInt8 Source # 
Instance details

Defined in ClickHaskell

Prim ChUInt8 Source # 
Instance details

Defined in ClickHaskell

FromChType ChUInt8 Word8 Source # 
Instance details

Defined in ClickHaskell

ToChType ChUInt8 Word8 Source # 
Instance details

Defined in ClickHaskell

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

type ToChTypeName ChUInt8 Source # 
Instance details

Defined in ClickHaskell

type ToChTypeName ChUInt8 = "UInt8"

newtype ChUInt16 Source #

ClickHouse UInt16 column type

Constructors

MkChUInt16 Word16 

Instances

Instances details
IsChType ChUInt16 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChUInt16 :: Symbol Source #

ToQueryPart ChUInt16 Source # 
Instance details

Defined in ClickHaskell

Bits ChUInt16 Source # 
Instance details

Defined in ClickHaskell

Bounded ChUInt16 Source # 
Instance details

Defined in ClickHaskell

Enum ChUInt16 Source # 
Instance details

Defined in ClickHaskell

Num ChUInt16 Source # 
Instance details

Defined in ClickHaskell

Integral ChUInt16 Source # 
Instance details

Defined in ClickHaskell

Real ChUInt16 Source # 
Instance details

Defined in ClickHaskell

Show ChUInt16 Source # 
Instance details

Defined in ClickHaskell

NFData ChUInt16 Source # 
Instance details

Defined in ClickHaskell

Methods

rnf :: ChUInt16 -> () #

Eq ChUInt16 Source # 
Instance details

Defined in ClickHaskell

Ord ChUInt16 Source # 
Instance details

Defined in ClickHaskell

Prim ChUInt16 Source # 
Instance details

Defined in ClickHaskell

FromChType ChUInt16 Word16 Source # 
Instance details

Defined in ClickHaskell

ToChType ChUInt16 Word16 Source # 
Instance details

Defined in ClickHaskell

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

type ToChTypeName ChUInt16 Source # 
Instance details

Defined in ClickHaskell

type ToChTypeName ChUInt16 = "UInt16"

newtype ChUInt32 Source #

ClickHouse UInt32 column type

Constructors

MkChUInt32 Word32 

Instances

Instances details
IsChType ChUInt32 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChUInt32 :: Symbol Source #

ToQueryPart ChUInt32 Source # 
Instance details

Defined in ClickHaskell

Bits ChUInt32 Source # 
Instance details

Defined in ClickHaskell

Bounded ChUInt32 Source # 
Instance details

Defined in ClickHaskell

Enum ChUInt32 Source # 
Instance details

Defined in ClickHaskell

Num ChUInt32 Source # 
Instance details

Defined in ClickHaskell

Integral ChUInt32 Source # 
Instance details

Defined in ClickHaskell

Real ChUInt32 Source # 
Instance details

Defined in ClickHaskell

Show ChUInt32 Source # 
Instance details

Defined in ClickHaskell

NFData ChUInt32 Source # 
Instance details

Defined in ClickHaskell

Methods

rnf :: ChUInt32 -> () #

Eq ChUInt32 Source # 
Instance details

Defined in ClickHaskell

Ord ChUInt32 Source # 
Instance details

Defined in ClickHaskell

Prim ChUInt32 Source # 
Instance details

Defined in ClickHaskell

FromChType ChUInt32 Word32 Source # 
Instance details

Defined in ClickHaskell

ToChType ChUInt32 Word32 Source # 
Instance details

Defined in ClickHaskell

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

type ToChTypeName ChUInt32 Source # 
Instance details

Defined in ClickHaskell

type ToChTypeName ChUInt32 = "UInt32"

newtype ChUInt64 Source #

ClickHouse UInt64 column type

Constructors

MkChUInt64 Word64 

Instances

Instances details
IsChType ChUInt64 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChUInt64 :: Symbol Source #

ToQueryPart ChUInt64 Source # 
Instance details

Defined in ClickHaskell

Bits ChUInt64 Source # 
Instance details

Defined in ClickHaskell

Bounded ChUInt64 Source # 
Instance details

Defined in ClickHaskell

Enum ChUInt64 Source # 
Instance details

Defined in ClickHaskell

Num ChUInt64 Source # 
Instance details

Defined in ClickHaskell

Integral ChUInt64 Source # 
Instance details

Defined in ClickHaskell

Real ChUInt64 Source # 
Instance details

Defined in ClickHaskell

Show ChUInt64 Source # 
Instance details

Defined in ClickHaskell

NFData ChUInt64 Source # 
Instance details

Defined in ClickHaskell

Methods

rnf :: ChUInt64 -> () #

Eq ChUInt64 Source # 
Instance details

Defined in ClickHaskell

Ord ChUInt64 Source # 
Instance details

Defined in ClickHaskell

Prim ChUInt64 Source # 
Instance details

Defined in ClickHaskell

FromChType ChUInt64 Word64 Source # 
Instance details

Defined in ClickHaskell

ToChType ChUInt64 Word64 Source # 
Instance details

Defined in ClickHaskell

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

type ToChTypeName ChUInt64 Source # 
Instance details

Defined in ClickHaskell

type ToChTypeName ChUInt64 = "UInt64"

newtype ChUInt128 Source #

ClickHouse UInt128 column type

Constructors

MkChUInt128 Word128 

Instances

Instances details
IsChType ChUInt128 Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChUInt128 :: Symbol Source #

ToQueryPart ChUInt128 Source # 
Instance details

Defined in ClickHaskell

Bits ChUInt128 Source # 
Instance details

Defined in ClickHaskell

Bounded ChUInt128 Source # 
Instance details

Defined in ClickHaskell

Enum ChUInt128 Source # 
Instance details

Defined in ClickHaskell

Num ChUInt128 Source # 
Instance details

Defined in ClickHaskell

Integral ChUInt128 Source # 
Instance details

Defined in ClickHaskell

Real ChUInt128 Source # 
Instance details

Defined in ClickHaskell

Show ChUInt128 Source # 
Instance details

Defined in ClickHaskell

NFData ChUInt128 Source # 
Instance details

Defined in ClickHaskell

Methods

rnf :: ChUInt128 -> () #

Eq ChUInt128 Source # 
Instance details

Defined in ClickHaskell

Ord ChUInt128 Source # 
Instance details

Defined in ClickHaskell

Prim ChUInt128 Source # 
Instance details

Defined in ClickHaskell

FromChType ChUInt128 Word128 Source # 
Instance details

Defined in ClickHaskell

ToChType ChUInt128 Word64 Source # 
Instance details

Defined in ClickHaskell

ToChType ChUInt128 Word128 Source # 
Instance details

Defined in ClickHaskell

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

type ToChTypeName ChUInt128 Source # 
Instance details

Defined in ClickHaskell

type ToChTypeName ChUInt128 = "UInt128"

newtype ChString Source #

ClickHouse String column type

Instances

Instances details
IsChType ChString Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChString :: Symbol Source #

IsLowCardinalitySupported ChString Source # 
Instance details

Defined in ClickHaskell

ToQueryPart ChString Source # 
Instance details

Defined in ClickHaskell

IsString ChString Source # 
Instance details

Defined in ClickHaskell

Show ChString Source # 
Instance details

Defined in ClickHaskell

NFData ChString Source # 
Instance details

Defined in ClickHaskell

Methods

rnf :: ChString -> () #

Eq ChString Source # 
Instance details

Defined in ClickHaskell

FromChType ChString StrictByteString Source # 
Instance details

Defined in ClickHaskell

(TypeError ('Text "ChString to Text using FromChType convertion could cause exception" ':$$: 'Text "Decode ByteString manually if you are sure it's always can be decoded or replace it with ByteString") :: Constraint) => FromChType ChString Text Source # 
Instance details

Defined in ClickHaskell

ToChType ChString Builder Source # 
Instance details

Defined in ClickHaskell

ToChType ChString StrictByteString Source # 
Instance details

Defined in ClickHaskell

ToChType ChString Text Source # 
Instance details

Defined in ClickHaskell

ToChType ChString String Source # 
Instance details

Defined in ClickHaskell

ToChType ChString Int Source # 
Instance details

Defined in ClickHaskell

IsString (LowCardinality ChString) Source # 
Instance details

Defined in ClickHaskell

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

type ToChTypeName ChString Source # 
Instance details

Defined in ClickHaskell

type ToChTypeName ChString = "String"

newtype ChUUID Source #

ClickHouse UUID column type

Constructors

MkChUUID Word128 

Instances

Instances details
IsChType ChUUID Source # 
Instance details

Defined in ClickHaskell

Associated Types

type ToChTypeName ChUUID :: Symbol Source #

ToQueryPart ChUUID Source # 
Instance details

Defined in ClickHaskell

Bounded ChUUID Source # 
Instance details

Defined in ClickHaskell

Enum ChUUID Source # 
Instance details

Defined in ClickHaskell

Generic ChUUID Source # 
Instance details

Defined in ClickHaskell

Associated Types

type Rep ChUUID :: Type -> Type #

Methods

from :: ChUUID -> Rep ChUUID x #

to :: Rep ChUUID x -> ChUUID #

Show ChUUID Source # 
Instance details

Defined in ClickHaskell

NFData ChUUID Source # 
Instance details

Defined in ClickHaskell

Methods

rnf :: ChUUID -> () #

Eq ChUUID Source # 
Instance details

Defined in ClickHaskell

Methods

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

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

Prim ChUUID Source # 
Instance details

Defined in ClickHaskell

ToChType ChUUID Word64 Source # 
Instance details

Defined in ClickHaskell

FromChType ChUUID (Word64, Word64) Source # 
Instance details

Defined in ClickHaskell

ToChType ChUUID (Word64, Word64) Source # 
Instance details

Defined in ClickHaskell

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

type ToChTypeName ChUUID Source # 
Instance details

Defined in ClickHaskell

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

Defined in ClickHaskell

newtype ChArray a Source #

Constructors

MkChArray [a] 

Instances

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

Defined in ClickHaskell

Associated Types

type ToChTypeName (ChArray chType) :: Symbol Source #

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

Defined in ClickHaskell

Methods

toQueryPart :: ChArray chType -> Builder Source #

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

Defined in ClickHaskell

Methods

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

show :: ChArray a -> String #

showList :: [ChArray a] -> ShowS #

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

Defined in ClickHaskell

Methods

rnf :: ChArray a -> () #

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

Defined in ClickHaskell

Methods

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

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

FromChType (ChArray chType) [chType] Source # 
Instance details

Defined in ClickHaskell

Methods

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

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

Defined in ClickHaskell

Methods

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

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

Defined in ClickHaskell

Methods

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

type ToChTypeName (ChArray chType) Source # 
Instance details

Defined in ClickHaskell

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

type Nullable = Maybe Source #

ClickHouse Nullable(T) column type (type synonym for Maybe)

data LowCardinality chType Source #

ClickHouse LowCardinality(T) column type

Instances

Instances details
IsLowCardinalitySupported chType => FromChType chType (LowCardinality chType) Source # 
Instance details

Defined in ClickHaskell

Methods

fromChType :: chType -> LowCardinality chType Source #

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

Defined in ClickHaskell

Methods

toChType :: LowCardinality chType -> chType Source #

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

Defined in ClickHaskell

Associated Types

type ToChTypeName (LowCardinality chType) :: Symbol Source #

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

Defined in ClickHaskell

IsString (LowCardinality ChString) Source # 
Instance details

Defined in ClickHaskell

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

Defined in ClickHaskell

Methods

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

show :: LowCardinality chType -> String #

showList :: [LowCardinality chType] -> ShowS #

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

Defined in ClickHaskell

Methods

rnf :: LowCardinality chType -> () #

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

Defined in ClickHaskell

Methods

(==) :: LowCardinality chType -> LowCardinality chType -> Bool #

(/=) :: LowCardinality chType -> LowCardinality chType -> Bool #

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

Defined in ClickHaskell

Methods

fromChType :: LowCardinality chType -> chType Source #

(FromChType chType outputType, IsChType (LowCardinality chType), IsLowCardinalitySupported chType) => FromChType (LowCardinality chType) outputType Source # 
Instance details

Defined in ClickHaskell

Methods

fromChType :: LowCardinality chType -> outputType Source #

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

Defined in ClickHaskell

Methods

toChType :: chType -> LowCardinality chType Source #

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

Defined in ClickHaskell

Methods

toChType :: chType -> LowCardinality inputType Source #

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

Defined in ClickHaskell

Methods

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

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

Defined in ClickHaskell

Methods

renderColumnName :: Builder Source #

renderColumnType :: Builder Source #

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

type ToChTypeName (LowCardinality chType) Source # 
Instance details

Defined in ClickHaskell

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

class IsChType chType => IsLowCardinalitySupported chType Source #

Instances

Instances details
IsLowCardinalitySupported ChString Source # 
Instance details

Defined in ClickHaskell

(IsChType chType, TypeError (((((('Text "LowCardinality(" ':<>: 'ShowType chType) ':<>: 'Text ") is unsupported") ':$$: 'Text "Use one of these types:") ':$$: 'Text " ChString") ':$$: 'Text " ChDateTime") ':$$: 'Text " Nullable(T)") :: Constraint) => IsLowCardinalitySupported chType Source # 
Instance details

Defined in ClickHaskell

(IsLowCardinalitySupported chType, IsChType (Nullable chType)) => IsLowCardinalitySupported (Nullable chType) Source # 
Instance details

Defined in ClickHaskell

newtype UVarInt Source #

Unsigned variable-length quantity encoding

Part of protocol implementation

Constructors

MkUVarInt Word64 

Instances

Instances details
Bits UVarInt Source # 
Instance details

Defined in ClickHaskell

Bounded UVarInt Source # 
Instance details

Defined in ClickHaskell

Enum UVarInt Source # 
Instance details

Defined in ClickHaskell

Num UVarInt Source # 
Instance details

Defined in ClickHaskell

Integral UVarInt Source # 
Instance details

Defined in ClickHaskell

Real UVarInt Source # 
Instance details

Defined in ClickHaskell

Show UVarInt Source # 
Instance details

Defined in ClickHaskell

NFData UVarInt Source # 
Instance details

Defined in ClickHaskell

Methods

rnf :: UVarInt -> () #

Eq UVarInt Source # 
Instance details

Defined in ClickHaskell

Methods

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

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

Ord UVarInt Source # 
Instance details

Defined in ClickHaskell

Prim UVarInt Source # 
Instance details

Defined in ClickHaskell

data Word128 #

Constructors

Word128 

Instances

Instances details
Data Word128 
Instance details

Defined in Data.WideWord.Word128

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word128 -> c Word128 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word128 #

toConstr :: Word128 -> Constr #

dataTypeOf :: Word128 -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Word128) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word128) #

gmapT :: (forall b. Data b => b -> b) -> Word128 -> Word128 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word128 -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word128 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Word128 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Word128 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word128 -> m Word128 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word128 -> m Word128 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word128 -> m Word128 #

Storable Word128 
Instance details

Defined in Data.WideWord.Word128

Bits Word128 
Instance details

Defined in Data.WideWord.Word128

FiniteBits Word128 
Instance details

Defined in Data.WideWord.Word128

Bounded Word128 
Instance details

Defined in Data.WideWord.Word128

Enum Word128 
Instance details

Defined in Data.WideWord.Word128

Generic Word128 
Instance details

Defined in Data.WideWord.Word128

Associated Types

type Rep Word128 :: Type -> Type #

Methods

from :: Word128 -> Rep Word128 x #

to :: Rep Word128 x -> Word128 #

Ix Word128 
Instance details

Defined in Data.WideWord.Word128

Num Word128 
Instance details

Defined in Data.WideWord.Word128

Read Word128 
Instance details

Defined in Data.WideWord.Word128

Integral Word128 
Instance details

Defined in Data.WideWord.Word128

Real Word128 
Instance details

Defined in Data.WideWord.Word128

Show Word128 
Instance details

Defined in Data.WideWord.Word128

Binary Word128

Since: wide-word-0.1.5.0

Instance details

Defined in Data.WideWord.Word128

Methods

put :: Word128 -> Put #

get :: Get Word128 #

putList :: [Word128] -> Put #

NFData Word128 
Instance details

Defined in Data.WideWord.Word128

Methods

rnf :: Word128 -> () #

Eq Word128 
Instance details

Defined in Data.WideWord.Word128

Methods

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

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

Ord Word128 
Instance details

Defined in Data.WideWord.Word128

Hashable Word128 
Instance details

Defined in Data.WideWord.Word128

Methods

hashWithSalt :: Int -> Word128 -> Int #

hash :: Word128 -> Int #

Prim Word128 
Instance details

Defined in Data.WideWord.Word128

FromChType ChUInt128 Word128 Source # 
Instance details

Defined in ClickHaskell

ToChType ChUInt128 Word128 Source # 
Instance details

Defined in ClickHaskell

type Rep Word128 
Instance details

Defined in Data.WideWord.Word128

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

data Int128 #

Constructors

Int128 

Instances

Instances details
Data Int128 
Instance details

Defined in Data.WideWord.Int128

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int128 -> c Int128 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int128 #

toConstr :: Int128 -> Constr #

dataTypeOf :: Int128 -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Int128) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int128) #

gmapT :: (forall b. Data b => b -> b) -> Int128 -> Int128 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int128 -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int128 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Int128 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Int128 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int128 -> m Int128 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int128 -> m Int128 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int128 -> m Int128 #

Storable Int128 
Instance details

Defined in Data.WideWord.Int128

Bits Int128 
Instance details

Defined in Data.WideWord.Int128

FiniteBits Int128 
Instance details

Defined in Data.WideWord.Int128

Bounded Int128 
Instance details

Defined in Data.WideWord.Int128

Enum Int128 
Instance details

Defined in Data.WideWord.Int128

Generic Int128 
Instance details

Defined in Data.WideWord.Int128

Associated Types

type Rep Int128 :: Type -> Type #

Methods

from :: Int128 -> Rep Int128 x #

to :: Rep Int128 x -> Int128 #

Ix Int128 
Instance details

Defined in Data.WideWord.Int128

Num Int128 
Instance details

Defined in Data.WideWord.Int128

Read Int128 
Instance details

Defined in Data.WideWord.Int128

Integral Int128 
Instance details

Defined in Data.WideWord.Int128

Real Int128 
Instance details

Defined in Data.WideWord.Int128

Show Int128 
Instance details

Defined in Data.WideWord.Int128

Binary Int128

Since: wide-word-0.1.5.0

Instance details

Defined in Data.WideWord.Int128

Methods

put :: Int128 -> Put #

get :: Get Int128 #

putList :: [Int128] -> Put #

NFData Int128 
Instance details

Defined in Data.WideWord.Int128

Methods

rnf :: Int128 -> () #

Eq Int128 
Instance details

Defined in Data.WideWord.Int128

Methods

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

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

Ord Int128 
Instance details

Defined in Data.WideWord.Int128

Hashable Int128 
Instance details

Defined in Data.WideWord.Int128

Methods

hashWithSalt :: Int -> Int128 -> Int #

hash :: Int128 -> Int #

Prim Int128 
Instance details

Defined in Data.WideWord.Int128

FromChType ChInt128 Int128 Source # 
Instance details

Defined in ClickHaskell

ToChType ChInt128 Int128 Source # 
Instance details

Defined in ClickHaskell

type Rep Int128 
Instance details

Defined in Data.WideWord.Int128

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