Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Database.DuckDB.Simple
Description
The API mirrors the ergonomics of sqlite-simple
while being backed by the
DuckDB C API. It supports connection management, parameter binding, execution,
and typed result decoding. See md
for usage examples.
Synopsis
- data Connection
- open :: FilePath -> IO Connection
- close :: Connection -> IO ()
- withConnection :: FilePath -> (Connection -> IO a) -> IO a
- newtype Query = Query {}
- data Statement
- openStatement :: Connection -> Query -> IO Statement
- closeStatement :: Statement -> IO ()
- withStatement :: Connection -> Query -> (Statement -> IO a) -> IO a
- clearStatementBindings :: Statement -> IO ()
- namedParameterIndex :: Statement -> Text -> IO (Maybe Int)
- columnCount :: Statement -> IO Int
- columnName :: Statement -> Int -> IO Text
- executeStatement :: Statement -> IO Int
- execute :: ToRow q => Connection -> Query -> q -> IO Int
- executeMany :: ToRow q => Connection -> Query -> [q] -> IO Int
- execute_ :: Connection -> Query -> IO Int
- bind :: Statement -> [FieldBinding] -> IO ()
- bindNamed :: Statement -> [NamedParam] -> IO ()
- executeNamed :: Connection -> Query -> [NamedParam] -> IO Int
- queryNamed :: FromRow r => Connection -> Query -> [NamedParam] -> IO [r]
- fold :: (FromRow row, ToRow params) => Connection -> Query -> params -> a -> (a -> row -> IO a) -> IO a
- fold_ :: FromRow row => Connection -> Query -> a -> (a -> row -> IO a) -> IO a
- foldNamed :: FromRow row => Connection -> Query -> [NamedParam] -> a -> (a -> row -> IO a) -> IO a
- withTransaction :: Connection -> IO a -> IO a
- query :: (ToRow q, FromRow r) => Connection -> Query -> q -> IO [r]
- queryWith :: ToRow q => RowParser r -> Connection -> Query -> q -> IO [r]
- query_ :: FromRow r => Connection -> Query -> IO [r]
- queryWith_ :: RowParser r -> Connection -> Query -> IO [r]
- nextRow :: FromRow r => Statement -> IO (Maybe r)
- nextRowWith :: RowParser r -> Statement -> IO (Maybe r)
- data SQLError = SQLError {}
- data FormatError = FormatError {
- formatErrorMessage :: !Text
- formatErrorQuery :: !Query
- formatErrorParams :: ![String]
- data ResultError
- = Incompatible {
- errSQLType :: Text
- errSQLField :: Text
- errHaskellType :: Text
- errMessage :: Text
- | UnexpectedNull {
- errSQLType :: Text
- errSQLField :: Text
- errHaskellType :: Text
- errMessage :: Text
- | ConversionFailed {
- errSQLType :: Text
- errSQLField :: Text
- errHaskellType :: Text
- errMessage :: Text
- = Incompatible {
- type FieldParser a = Field -> Ok a
- class FromField a where
- fromField :: FieldParser a
- class FromRow a where
- data RowParser a
- field :: FromField a => RowParser a
- fieldWith :: FieldParser a -> RowParser a
- numFieldsRemaining :: RowParser Int
- class ToField a where
- toField :: a -> FieldBinding
- class ToRow a where
- toRow :: a -> [FieldBinding]
- data FieldBinding
- data NamedParam where
- (:=) :: ToField a => Text -> a -> NamedParam
- data Null = Null
- newtype Only a = Only {
- fromOnly :: a
- data h :. t = h :. t
- class Function a
- createFunction :: forall f. Function f => Connection -> Text -> f -> IO ()
- deleteFunction :: Connection -> Text -> IO ()
Connections
data Connection Source #
Tracks the lifetime of a DuckDB database and connection pair.
close :: Connection -> IO () Source #
Close a connection. The operation is idempotent.
withConnection :: FilePath -> (Connection -> IO a) -> IO a Source #
Run an action with a freshly opened connection, closing it afterwards.
Queries and statements
Represents a textual SQL query with UTF-8 encoding semantics.
Constructors
Query | |
openStatement :: Connection -> Query -> IO Statement Source #
Prepare a SQL statement for execution.
closeStatement :: Statement -> IO () Source #
Finalise a prepared statement. The operation is idempotent.
withStatement :: Connection -> Query -> (Statement -> IO a) -> IO a Source #
Run an action with a prepared statement, closing it afterwards.
clearStatementBindings :: Statement -> IO () Source #
Remove all parameter bindings associated with a prepared statement.
namedParameterIndex :: Statement -> Text -> IO (Maybe Int) Source #
Look up the 1-based index of a named placeholder.
columnCount :: Statement -> IO Int Source #
Retrieve the number of columns produced by the supplied prepared statement.
columnName :: Statement -> Int -> IO Text Source #
Look up the zero-based column name exposed by a prepared statement result.
executeStatement :: Statement -> IO Int Source #
Execute a prepared statement and return the number of affected rows.
Resets any active result stream before running and raises a SqlError
if DuckDB reports a failure.
execute :: ToRow q => Connection -> Query -> q -> IO Int Source #
Execute a query with positional parameters and return the affected row count.
executeMany :: ToRow q => Connection -> Query -> [q] -> IO Int Source #
Execute the same query multiple times with different parameter sets.
execute_ :: Connection -> Query -> IO Int Source #
Execute an ad-hoc query without parameters and return the affected row count.
bind :: Statement -> [FieldBinding] -> IO () Source #
Bind positional parameters to a prepared statement, replacing any previous bindings.
bindNamed :: Statement -> [NamedParam] -> IO () Source #
Bind named parameters to a prepared statement, preserving any positional bindings.
executeNamed :: Connection -> Query -> [NamedParam] -> IO Int Source #
Execute a query that uses named parameters.
queryNamed :: FromRow r => Connection -> Query -> [NamedParam] -> IO [r] Source #
Run a query that uses named parameters and decode all rows eagerly.
fold :: (FromRow row, ToRow params) => Connection -> Query -> params -> a -> (a -> row -> IO a) -> IO a Source #
Stream a parameterised query through an accumulator without loading all rows. Bind the supplied parameters, start a streaming result, and apply the step function row by row to produce a final accumulator value.
fold_ :: FromRow row => Connection -> Query -> a -> (a -> row -> IO a) -> IO a Source #
Stream a parameterless query through an accumulator without loading all rows.
foldNamed :: FromRow row => Connection -> Query -> [NamedParam] -> a -> (a -> row -> IO a) -> IO a Source #
Stream a query that uses named parameters through an accumulator.
withTransaction :: Connection -> IO a -> IO a Source #
Run an action inside a transaction.
query :: (ToRow q, FromRow r) => Connection -> Query -> q -> IO [r] Source #
Run a parameterised query and decode every resulting row eagerly.
queryWith :: ToRow q => RowParser r -> Connection -> Query -> q -> IO [r] Source #
Run a parameterised query with a custom row parser.
query_ :: FromRow r => Connection -> Query -> IO [r] Source #
Run a query without supplying parameters and decode all rows eagerly.
queryWith_ :: RowParser r -> Connection -> Query -> IO [r] Source #
Run a query without parameters using a custom row parser.
nextRow :: FromRow r => Statement -> IO (Maybe r) Source #
Fetch the next row from a streaming statement, stopping when no rows remain.
nextRowWith :: RowParser r -> Statement -> IO (Maybe r) Source #
Fetch the next row using a custom parser, returning Nothing
once exhausted.
Errors and conversions
Represents an error reported by DuckDB or by duckdb-simple itself.
Constructors
SQLError | |
Fields |
Instances
Exception SQLError Source # | |
Defined in Database.DuckDB.Simple.Internal Methods toException :: SQLError -> SomeException # fromException :: SomeException -> Maybe SQLError # displayException :: SQLError -> String # | |
Show SQLError Source # | |
Eq SQLError Source # | |
data FormatError Source #
Raised when parameter formatting fails before a statement is executed.
Constructors
FormatError | |
Fields
|
Instances
Exception FormatError Source # | |
Defined in Database.DuckDB.Simple.Types Methods toException :: FormatError -> SomeException # fromException :: SomeException -> Maybe FormatError # displayException :: FormatError -> String # | |
Show FormatError Source # | |
Defined in Database.DuckDB.Simple.Types Methods showsPrec :: Int -> FormatError -> ShowS # show :: FormatError -> String # showList :: [FormatError] -> ShowS # | |
Eq FormatError Source # | |
Defined in Database.DuckDB.Simple.Types |
data ResultError Source #
Exception thrown if conversion from a SQL value to a Haskell value fails.
Constructors
Incompatible | The SQL and Haskell types are not compatible. |
Fields
| |
UnexpectedNull | A SQL |
Fields
| |
ConversionFailed | The SQL value could not be parsed, or could not be represented as a valid Haskell value, or an unexpected low-level error occurred (e.g. mismatch between metadata and actual data in a row). |
Fields
|
Instances
Exception ResultError Source # | |
Defined in Database.DuckDB.Simple.FromField Methods toException :: ResultError -> SomeException # fromException :: SomeException -> Maybe ResultError # displayException :: ResultError -> String # | |
Show ResultError Source # | |
Defined in Database.DuckDB.Simple.FromField Methods showsPrec :: Int -> ResultError -> ShowS # show :: ResultError -> String # showList :: [ResultError] -> ShowS # | |
Eq ResultError Source # | |
Defined in Database.DuckDB.Simple.FromField |
type FieldParser a = Field -> Ok a Source #
Parser used by FromField
instances and utilities such as
fieldWith
. The supplied Field
contains
column metadata and an already-decoded FieldValue
; callers should return
Ok
on success or Errors
(typically wrapping a ResultError
) when the
conversion fails.
class FromField a where Source #
Types that can be constructed from a DuckDB column.
Methods
fromField :: FieldParser a Source #
Instances
class FromRow a where Source #
Types that can be constructed from database rows.
Minimal complete definition
Nothing
Methods
Instances
Parser used by FromRow
implementations.
field :: FromField a => RowParser a Source #
Pull the next field and parse it using its FromField
instance.
fieldWith :: FieldParser a -> RowParser a Source #
Pull the next field using the provided FieldParser
.
numFieldsRemaining :: RowParser Int Source #
Report how many columns remain unread in the current row.
class ToField a where Source #
Types that can be used as positional parameters.
Methods
toField :: a -> FieldBinding Source #
Instances
Types that can be transformed into parameter bindings.
Minimal complete definition
Nothing
Methods
toRow :: a -> [FieldBinding] Source #
Instances
data FieldBinding Source #
Encapsulates the action required to bind a single positional parameter, together with a textual description used in diagnostics.
data NamedParam where Source #
Represents a named parameter binding using the :=
operator.
Constructors
(:=) :: ToField a => Text -> a -> NamedParam infixr 3 |
Placeholder representing SQL NULL
.
Constructors
Null |
Wrapper used for single-column rows.
Instances
Convenience product type for combining FromRow
/ToRow
instances.
Constructors
h :. t infixr 3 |
Instances
(Read h, Read t) => Read (h :. t) Source # | |
(Show h, Show t) => Show (h :. t) Source # | |
(FromRow a, FromRow b) => FromRow (a :. b) Source # | |
(ToRow a, ToRow b) => ToRow (a :. b) Source # | |
Defined in Database.DuckDB.Simple.ToRow Methods toRow :: (a :. b) -> [FieldBinding] Source # | |
(Eq h, Eq t) => Eq (h :. t) Source # | |
(Ord h, Ord t) => Ord (h :. t) Source # | |
Defined in Database.DuckDB.Simple.Types |
User-defined scalar functions
Typeclass describing Haskell functions that can be exposed to DuckDB.
Minimal complete definition
argumentTypes, returnType, isVolatile, applyFunction
Instances
FunctionResult a => Function a Source # | |
Defined in Database.DuckDB.Simple.Function Methods argumentTypes :: Proxy a -> [DuckDBType] returnType :: Proxy a -> ScalarType isVolatile :: Proxy a -> Bool applyFunction :: [Field] -> a -> IO ScalarValue | |
FunctionResult a => Function (IO a) Source # | |
Defined in Database.DuckDB.Simple.Function Methods argumentTypes :: Proxy (IO a) -> [DuckDBType] returnType :: Proxy (IO a) -> ScalarType isVolatile :: Proxy (IO a) -> Bool applyFunction :: [Field] -> IO a -> IO ScalarValue | |
(FromField a, FunctionArg a, Function r) => Function (a -> r) Source # | |
Defined in Database.DuckDB.Simple.Function Methods argumentTypes :: Proxy (a -> r) -> [DuckDBType] returnType :: Proxy (a -> r) -> ScalarType isVolatile :: Proxy (a -> r) -> Bool applyFunction :: [Field] -> (a -> r) -> IO ScalarValue |
createFunction :: forall f. Function f => Connection -> Text -> f -> IO () Source #
Register a Haskell function under the supplied name.
deleteFunction :: Connection -> Text -> IO () Source #
Drop a previously registered scalar function by issuing a DROP FUNCTION statement.