Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data ChCredential = MkChCredential {
- chLogin :: Text
- chPass :: Text
- chDatabase :: Text
- chHost :: HostName
- chPort :: ServiceName
- defaultCredentials :: ChCredential
- data Connection = MkConnection {
- sock :: Socket
- user :: ChString
- bufferSize :: Int64
- revision :: ProtocolRevision
- openNativeConnection :: HasCallStack => ChCredential -> IO Connection
- data Table (name :: Symbol) (columns :: [Type])
- data Columns (columns :: [Type])
- data Column (name :: Symbol) (chType :: Type)
- class (IsChType (GetColumnType column), KnownSymbol (GetColumnName column)) => KnownColumn column where
- renderColumnName :: Builder
- renderColumnType :: Builder
- mkColumn :: UVarInt -> [GetColumnType column] -> Column (GetColumnName column) (GetColumnType column)
- class DeserializableColumn column where
- deserializeColumn :: ProtocolRevision -> UVarInt -> Get column
- class (HasColumns hasColumns, DeserializableColumns (Columns (GetColumns hasColumns))) => ReadableFrom hasColumns record where
- deserializeColumns :: ProtocolRevision -> UVarInt -> Get [record]
- readingColumns :: Builder
- select :: forall columns record. ReadableFrom (Columns columns) record => Connection -> ChString -> IO [record]
- selectFrom :: forall table record name columns. (table ~ Table name columns, KnownSymbol name, ReadableFrom table record) => Connection -> IO [record]
- selectFromView :: forall view record name columns parameters passedParameters. (ReadableFrom view record, KnownSymbol name, view ~ View name columns parameters, CheckParameters parameters passedParameters) => Connection -> (Parameters '[] -> Parameters passedParameters) -> IO [record]
- data View (name :: Symbol) (columns :: [Type]) (parameters :: [Type])
- parameter :: forall name chType parameters userType. (InterpretableParameters parameters, ToChType chType userType, KnownSymbol name, ToQueryPart chType) => userType -> Parameters parameters -> WithPassedParameter (Parameter name chType) parameters
- data Parameter (name :: Symbol) (chType :: Type)
- streamSelect :: forall columns record a. (ReadableFrom (Columns columns) record, NFData a) => Connection -> ChString -> ([record] -> IO [a]) -> IO [a]
- streamSelectFrom :: forall table record name columns a. (table ~ Table name columns, KnownSymbol name, ReadableFrom table record, NFData a) => Connection -> ([record] -> IO [a]) -> IO [a]
- streamSelectFromView :: forall view record name columns parameters passedParameters a. (ReadableFrom view record, KnownSymbol name, view ~ View name columns parameters, NFData a, CheckParameters parameters passedParameters) => Connection -> (Parameters '[] -> Parameters passedParameters) -> ([record] -> IO [a]) -> IO [a]
- handleSelect :: forall hasColumns record a. ReadableFrom hasColumns record => Connection -> Buffer -> ([record] -> IO [a]) -> IO [a]
- class (HasColumns (Columns (GetColumns columns)), Serializable (Columns (GetColumns columns)), DeserializableColumns (Columns (GetColumns columns))) => WritableInto columns record where
- serializeRecords :: ProtocolRevision -> UVarInt -> [record] -> Builder
- writingColumns :: Builder
- columnsCount :: UVarInt
- insertInto :: forall table record name columns. (table ~ Table name columns, WritableInto table record, KnownSymbol name) => Connection -> [record] -> IO ()
- ping :: HasCallStack => Connection -> IO ()
Connection
data ChCredential Source #
MkChCredential | |
|
data Connection Source #
MkConnection | |
|
Reading and writing
data Columns (columns :: [Type]) Source #
Instances
(Serializable (Columns columns), Serializable col) => Serializable (Columns (col ': columns)) Source # | |
Defined in ClickHaskell.Columns | |
Serializable (Columns ('[] :: [Type])) Source # | |
Defined in ClickHaskell.Columns |
data Column (name :: Symbol) (chType :: Type) Source #
Column declaration
For example:
type MyColumn = Column "myColumn" ChString
Instances
class (IsChType (GetColumnType column), KnownSymbol (GetColumnName column)) => KnownColumn column where Source #
renderColumnName :: Builder Source #
renderColumnType :: Builder Source #
mkColumn :: UVarInt -> [GetColumnType column] -> Column (GetColumnName column) (GetColumnType column) Source #
Instances
class DeserializableColumn column where Source #
deserializeColumn :: ProtocolRevision -> UVarInt -> Get column Source #
Instances
Reading
class (HasColumns hasColumns, DeserializableColumns (Columns (GetColumns hasColumns))) => ReadableFrom hasColumns record where Source #
Nothing
deserializeColumns :: ProtocolRevision -> UVarInt -> Get [record] Source #
default deserializeColumns :: GenericReadable record hasColumns => ProtocolRevision -> UVarInt -> Get [record] Source #
readingColumns :: Builder Source #
default readingColumns :: GenericReadable record hasColumns => Builder Source #
Simple
select :: forall columns record. ReadableFrom (Columns columns) record => Connection -> ChString -> IO [record] Source #
selectFrom :: forall table record name columns. (table ~ Table name columns, KnownSymbol name, ReadableFrom table record) => Connection -> IO [record] Source #
selectFromView :: forall view record name columns parameters passedParameters. (ReadableFrom view record, KnownSymbol name, view ~ View name columns parameters, CheckParameters parameters passedParameters) => Connection -> (Parameters '[] -> Parameters passedParameters) -> IO [record] Source #
parameter :: forall name chType parameters userType. (InterpretableParameters parameters, ToChType chType userType, KnownSymbol name, ToQueryPart chType) => userType -> Parameters parameters -> WithPassedParameter (Parameter name chType) parameters Source #
Streaming
streamSelect :: forall columns record a. (ReadableFrom (Columns columns) record, NFData a) => Connection -> ChString -> ([record] -> IO [a]) -> IO [a] Source #
streamSelectFrom :: forall table record name columns a. (table ~ Table name columns, KnownSymbol name, ReadableFrom table record, NFData a) => Connection -> ([record] -> IO [a]) -> IO [a] Source #
streamSelectFromView :: forall view record name columns parameters passedParameters a. (ReadableFrom view record, KnownSymbol name, view ~ View name columns parameters, NFData a, CheckParameters parameters passedParameters) => Connection -> (Parameters '[] -> Parameters passedParameters) -> ([record] -> IO [a]) -> IO [a] Source #
Internal
handleSelect :: forall hasColumns record a. ReadableFrom hasColumns record => Connection -> Buffer -> ([record] -> IO [a]) -> IO [a] Source #
Writing
class (HasColumns (Columns (GetColumns columns)), Serializable (Columns (GetColumns columns)), DeserializableColumns (Columns (GetColumns columns))) => WritableInto columns record where Source #
Nothing
serializeRecords :: ProtocolRevision -> UVarInt -> [record] -> Builder Source #
default serializeRecords :: GenericWritable record (GetColumns columns) => ProtocolRevision -> UVarInt -> [record] -> Builder Source #
writingColumns :: Builder Source #
default writingColumns :: GenericWritable record (GetColumns columns) => Builder Source #
columnsCount :: UVarInt Source #
default columnsCount :: GenericWritable record (GetColumns columns) => UVarInt Source #
insertInto :: forall table record name columns. (table ~ Table name columns, WritableInto table record, KnownSymbol name) => Connection -> [record] -> IO () Source #
Ping database connection
ping :: HasCallStack => Connection -> IO () Source #