Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Database.DuckDB.Value
Synopsis
- type DuckDBResult = Ptr DuckDBResult
- data DuckDBDataChunk
- data DuckDBVector
- type DuckDBType = Int32
- data DuckDBLogicalType
- destroy :: DuckDBResult -> DuckDBMonad ()
- pattern DUCKDB_TYPE_INVALID :: DuckDBType
- pattern DUCKDB_TYPE_BOOLEAN :: DuckDBType
- pattern DUCKDB_TYPE_TINYINT :: DuckDBType
- pattern DUCKDB_TYPE_SMALLINT :: DuckDBType
- pattern DUCKDB_TYPE_INTEGER :: DuckDBType
- pattern DUCKDB_TYPE_BIGINT :: DuckDBType
- pattern DUCKDB_TYPE_UTINYINT :: DuckDBType
- pattern DUCKDB_TYPE_USMALLINT :: DuckDBType
- pattern DUCKDB_TYPE_UINTEGER :: DuckDBType
- pattern DUCKDB_TYPE_UBIGINT :: DuckDBType
- pattern DUCKDB_TYPE_FLOAT :: DuckDBType
- pattern DUCKDB_TYPE_DOUBLE :: DuckDBType
- pattern DUCKDB_TYPE_TIMESTAMP :: DuckDBType
- pattern DUCKDB_TYPE_DATE :: DuckDBType
- pattern DUCKDB_TYPE_TIME :: DuckDBType
- pattern DUCKDB_TYPE_INTERVAL :: DuckDBType
- pattern DUCKDB_TYPE_HUGEINT :: DuckDBType
- pattern DUCKDB_TYPE_VARCHAR :: DuckDBType
- pattern DUCKDB_TYPE_BLOB :: DuckDBType
- pattern DUCKDB_TYPE_DECIMAL :: DuckDBType
- pattern DUCKDB_TYPE_TIMESTAMP_S :: DuckDBType
- pattern DUCKDB_TYPE_TIMESTAMP_MS :: DuckDBType
- pattern DUCKDB_TYPE_TIMESTAMP_NS :: DuckDBType
- pattern DUCKDB_TYPE_ENUM :: DuckDBType
- pattern DUCKDB_TYPE_LIST :: DuckDBType
- pattern DUCKDB_TYPE_STRUCT :: DuckDBType
- pattern DUCKDB_TYPE_MAP :: DuckDBType
- pattern DUCKDB_TYPE_UUID :: DuckDBType
- pattern DUCKDB_TYPE_UNION :: DuckDBType
- pattern DUCKDB_TYPE_BIT :: DuckDBType
- typeRep :: DuckDBType -> TypeRep
- data Int8
- data Int16
- data Int32
- data Int64
- data Word8
- data Word16
- data Word32
- data Word64
- type DuckDBDate = Int32
- type DuckDBTime = Int64
- type DuckDBTimestamp = Int64
- columnName :: DuckDBResult -> Int -> DuckDBMonad String
- columnType :: DuckDBResult -> Int -> DuckDBMonad DuckDBType
- columnLogicalType :: DuckDBResult -> Int -> DuckDBMonad DuckDBLogicalType
- columnCount :: DuckDBResult -> DuckDBMonad Int
- rowCount :: DuckDBResult -> DuckDBMonad Int
- rowsChanged :: DuckDBResult -> DuckDBMonad Int
- columnData :: DuckDBResult -> Int -> DuckDBMonad (Ptr a)
- nullmaskData :: DuckDBResult -> Int -> DuckDBMonad (Ptr Bool)
- chunkAt :: DuckDBResult -> Int -> DuckDBMonad DuckDBDataChunk
- isStreaming :: DuckDBResult -> DuckDBMonad Bool
- chunkCount :: DuckDBResult -> DuckDBMonad Int
- createChunk :: [DuckDBLogicalType] -> Int -> DuckDBMonad DuckDBDataChunk
- destroyChunk :: DuckDBDataChunk -> DuckDBMonad ()
- resetChunk :: DuckDBDataChunk -> DuckDBMonad ()
- getChunkColumnCount :: DuckDBDataChunk -> DuckDBMonad Int
- getChunkVector :: DuckDBDataChunk -> Int -> DuckDBMonad DuckDBVector
- getChunkSize :: DuckDBDataChunk -> DuckDBMonad Int
- setChunkSize :: DuckDBDataChunk -> Int -> DuckDBMonad ()
- getVectorType :: DuckDBVector -> DuckDBMonad DuckDBLogicalType
- getVectorData :: DuckDBVector -> DuckDBMonad (Ptr a)
- getVectorValidity :: DuckDBVector -> DuckDBMonad (Ptr Word64)
- ensureVectorValidityWritable :: DuckDBVector -> DuckDBMonad ()
- setVectorStringValue :: DuckDBVector -> Int -> String -> DuckDBMonad ()
- isValidityRowValid :: Ptr Word64 -> Int -> DuckDBMonad Bool
- setValidityRow :: Ptr Word64 -> Int -> Bool -> DuckDBMonad ()
- setValidityRowInvalid :: Ptr Word64 -> Int -> DuckDBMonad ()
- setValidityRowValid :: Ptr Word64 -> Int -> DuckDBMonad ()
- valueBoolean :: DuckDBResult -> Int -> Int -> DuckDBMonad Bool
- valueInt8 :: DuckDBResult -> Int -> Int -> DuckDBMonad Int8
- valueInt16 :: DuckDBResult -> Int -> Int -> DuckDBMonad Int16
- valueInt32 :: DuckDBResult -> Int -> Int -> DuckDBMonad Int32
- valueInt64 :: DuckDBResult -> Int -> Int -> DuckDBMonad Int64
- valueUint8 :: DuckDBResult -> Int -> Int -> DuckDBMonad Word8
- valueUint16 :: DuckDBResult -> Int -> Int -> DuckDBMonad Word16
- valueUint32 :: DuckDBResult -> Int -> Int -> DuckDBMonad Word32
- valueUint64 :: DuckDBResult -> Int -> Int -> DuckDBMonad Word64
- valueFloat :: DuckDBResult -> Int -> Int -> DuckDBMonad Float
- valueDouble :: DuckDBResult -> Int -> Int -> DuckDBMonad Double
- valueDate :: DuckDBResult -> Int -> Int -> DuckDBMonad DuckDBDate
- valueTime :: DuckDBResult -> Int -> Int -> DuckDBMonad DuckDBTime
- valueTimestamp :: DuckDBResult -> Int -> Int -> DuckDBMonad DuckDBTimestamp
- valueVarChar :: DuckDBResult -> Int -> Int -> DuckDBMonad String
- valueVarCharInternal :: DuckDBResult -> Int -> Int -> DuckDBMonad CString
- valueIsNull :: DuckDBResult -> Int -> Int -> DuckDBMonad Bool
Query result
type DuckDBResult = Ptr DuckDBResult Source #
data DuckDBDataChunk Source #
Instances
Storable DuckDBDataChunk Source # | |
Defined in Database.DuckDB.Internal.FFI Methods sizeOf :: DuckDBDataChunk -> Int # alignment :: DuckDBDataChunk -> Int # peekElemOff :: Ptr DuckDBDataChunk -> Int -> IO DuckDBDataChunk # pokeElemOff :: Ptr DuckDBDataChunk -> Int -> DuckDBDataChunk -> IO () # peekByteOff :: Ptr b -> Int -> IO DuckDBDataChunk # pokeByteOff :: Ptr b -> Int -> DuckDBDataChunk -> IO () # peek :: Ptr DuckDBDataChunk -> IO DuckDBDataChunk # poke :: Ptr DuckDBDataChunk -> DuckDBDataChunk -> IO () # | |
Eq DuckDBDataChunk Source # | |
Defined in Database.DuckDB.Internal.FFI Methods (==) :: DuckDBDataChunk -> DuckDBDataChunk -> Bool # (/=) :: DuckDBDataChunk -> DuckDBDataChunk -> Bool # |
data DuckDBVector Source #
Instances
Storable DuckDBVector Source # | |
Defined in Database.DuckDB.Internal.FFI Methods sizeOf :: DuckDBVector -> Int # alignment :: DuckDBVector -> Int # peekElemOff :: Ptr DuckDBVector -> Int -> IO DuckDBVector # pokeElemOff :: Ptr DuckDBVector -> Int -> DuckDBVector -> IO () # peekByteOff :: Ptr b -> Int -> IO DuckDBVector # pokeByteOff :: Ptr b -> Int -> DuckDBVector -> IO () # peek :: Ptr DuckDBVector -> IO DuckDBVector # poke :: Ptr DuckDBVector -> DuckDBVector -> IO () # | |
Eq DuckDBVector Source # | |
Defined in Database.DuckDB.Internal.FFI |
type DuckDBType = Int32 Source #
data DuckDBLogicalType Source #
Instances
Storable DuckDBLogicalType Source # | |
Defined in Database.DuckDB.Internal.FFI Methods sizeOf :: DuckDBLogicalType -> Int # alignment :: DuckDBLogicalType -> Int # peekElemOff :: Ptr DuckDBLogicalType -> Int -> IO DuckDBLogicalType # pokeElemOff :: Ptr DuckDBLogicalType -> Int -> DuckDBLogicalType -> IO () # peekByteOff :: Ptr b -> Int -> IO DuckDBLogicalType # pokeByteOff :: Ptr b -> Int -> DuckDBLogicalType -> IO () # peek :: Ptr DuckDBLogicalType -> IO DuckDBLogicalType # poke :: Ptr DuckDBLogicalType -> DuckDBLogicalType -> IO () # | |
Eq DuckDBLogicalType Source # | |
Defined in Database.DuckDB.Internal.FFI Methods (==) :: DuckDBLogicalType -> DuckDBLogicalType -> Bool # (/=) :: DuckDBLogicalType -> DuckDBLogicalType -> Bool # |
destroy :: DuckDBResult -> DuckDBMonad () Source #
Data types
pattern DUCKDB_TYPE_INVALID :: DuckDBType Source #
pattern DUCKDB_TYPE_BOOLEAN :: DuckDBType Source #
pattern DUCKDB_TYPE_TINYINT :: DuckDBType Source #
pattern DUCKDB_TYPE_SMALLINT :: DuckDBType Source #
pattern DUCKDB_TYPE_INTEGER :: DuckDBType Source #
pattern DUCKDB_TYPE_BIGINT :: DuckDBType Source #
pattern DUCKDB_TYPE_UTINYINT :: DuckDBType Source #
pattern DUCKDB_TYPE_USMALLINT :: DuckDBType Source #
pattern DUCKDB_TYPE_UINTEGER :: DuckDBType Source #
pattern DUCKDB_TYPE_UBIGINT :: DuckDBType Source #
pattern DUCKDB_TYPE_FLOAT :: DuckDBType Source #
pattern DUCKDB_TYPE_DOUBLE :: DuckDBType Source #
pattern DUCKDB_TYPE_TIMESTAMP :: DuckDBType Source #
pattern DUCKDB_TYPE_DATE :: DuckDBType Source #
pattern DUCKDB_TYPE_TIME :: DuckDBType Source #
pattern DUCKDB_TYPE_INTERVAL :: DuckDBType Source #
pattern DUCKDB_TYPE_HUGEINT :: DuckDBType Source #
pattern DUCKDB_TYPE_VARCHAR :: DuckDBType Source #
pattern DUCKDB_TYPE_BLOB :: DuckDBType Source #
pattern DUCKDB_TYPE_DECIMAL :: DuckDBType Source #
pattern DUCKDB_TYPE_TIMESTAMP_S :: DuckDBType Source #
pattern DUCKDB_TYPE_TIMESTAMP_MS :: DuckDBType Source #
pattern DUCKDB_TYPE_TIMESTAMP_NS :: DuckDBType Source #
pattern DUCKDB_TYPE_ENUM :: DuckDBType Source #
pattern DUCKDB_TYPE_LIST :: DuckDBType Source #
pattern DUCKDB_TYPE_STRUCT :: DuckDBType Source #
pattern DUCKDB_TYPE_MAP :: DuckDBType Source #
pattern DUCKDB_TYPE_UUID :: DuckDBType Source #
pattern DUCKDB_TYPE_UNION :: DuckDBType Source #
pattern DUCKDB_TYPE_BIT :: DuckDBType Source #
typeRep :: DuckDBType -> TypeRep 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
8-bit unsigned integer type
Instances
16-bit unsigned integer type
Instances
32-bit unsigned integer type
Instances
64-bit unsigned integer type
Instances
type DuckDBDate = Int32 Source #
type DuckDBTime = Int64 Source #
type DuckDBTimestamp = Int64 Source #
Columns
columnName :: DuckDBResult -> Int -> DuckDBMonad String Source #
columnType :: DuckDBResult -> Int -> DuckDBMonad DuckDBType Source #
columnCount :: DuckDBResult -> DuckDBMonad Int Source #
rowCount :: DuckDBResult -> DuckDBMonad Int Source #
rowsChanged :: DuckDBResult -> DuckDBMonad Int Source #
columnData :: DuckDBResult -> Int -> DuckDBMonad (Ptr a) Source #
nullmaskData :: DuckDBResult -> Int -> DuckDBMonad (Ptr Bool) Source #
Data chunks
chunkAt :: DuckDBResult -> Int -> DuckDBMonad DuckDBDataChunk Source #
chunkCount :: DuckDBResult -> DuckDBMonad Int Source #
Arguments
:: [DuckDBLogicalType] | |
-> Int | column count |
-> DuckDBMonad DuckDBDataChunk |
destroyChunk :: DuckDBDataChunk -> DuckDBMonad () Source #
resetChunk :: DuckDBDataChunk -> DuckDBMonad () Source #
setChunkSize :: DuckDBDataChunk -> Int -> DuckDBMonad () Source #
getVectorData :: DuckDBVector -> DuckDBMonad (Ptr a) Source #
getVectorValidity :: DuckDBVector -> DuckDBMonad (Ptr Word64) Source #
setVectorStringValue :: DuckDBVector -> Int -> String -> DuckDBMonad () Source #
isValidityRowValid :: Ptr Word64 -> Int -> DuckDBMonad Bool Source #
setValidityRow :: Ptr Word64 -> Int -> Bool -> DuckDBMonad () Source #
setValidityRowInvalid :: Ptr Word64 -> Int -> DuckDBMonad () Source #
setValidityRowValid :: Ptr Word64 -> Int -> DuckDBMonad () Source #
Element values
Arguments
:: DuckDBResult | |
-> Int | column |
-> Int | row |
-> DuckDBMonad Bool |
Arguments
:: DuckDBResult | |
-> Int | column |
-> Int | row |
-> DuckDBMonad Int8 |
Arguments
:: DuckDBResult | |
-> Int | column |
-> Int | row |
-> DuckDBMonad Int16 |
Arguments
:: DuckDBResult | |
-> Int | column |
-> Int | row |
-> DuckDBMonad Int32 |
Arguments
:: DuckDBResult | |
-> Int | column |
-> Int | row |
-> DuckDBMonad Int64 |
Arguments
:: DuckDBResult | |
-> Int | column |
-> Int | row |
-> DuckDBMonad Word8 |
Arguments
:: DuckDBResult | |
-> Int | column |
-> Int | row |
-> DuckDBMonad Word16 |
Arguments
:: DuckDBResult | |
-> Int | column |
-> Int | row |
-> DuckDBMonad Word32 |
Arguments
:: DuckDBResult | |
-> Int | column |
-> Int | row |
-> DuckDBMonad Word64 |
Arguments
:: DuckDBResult | |
-> Int | column |
-> Int | row |
-> DuckDBMonad Float |
Arguments
:: DuckDBResult | |
-> Int | column |
-> Int | row |
-> DuckDBMonad Double |
Arguments
:: DuckDBResult | |
-> Int | column |
-> Int | row |
-> DuckDBMonad DuckDBDate |
Arguments
:: DuckDBResult | |
-> Int | column |
-> Int | row |
-> DuckDBMonad DuckDBTime |
Arguments
:: DuckDBResult | |
-> Int | column |
-> Int | row |
-> DuckDBMonad DuckDBTimestamp |
Arguments
:: DuckDBResult | |
-> Int | column |
-> Int | row |
-> DuckDBMonad String |
Arguments
:: DuckDBResult | |
-> Int | column |
-> Int | row |
-> DuckDBMonad CString |
Arguments
:: DuckDBResult | |
-> Int | column |
-> Int | row |
-> DuckDBMonad Bool |