Copyright | (c) Ole Krüger 2016 |
---|---|
License | BSD3 |
Maintainer | Ole Krüger <ole@vprsm.de> |
Safe Haskell | None |
Language | Haskell2010 |
- data Errand a
- runErrand :: Connection -> Errand a -> IO (Either ErrandError a)
- execute :: ErrandQuery q Result => q r -> ErrandResult q Result
- execute' :: ErrandQuery q Int => q r -> ErrandResult q Int
- query :: (Entity r, ErrandQuery q [r]) => q r -> ErrandResult q [r]
- queryWith :: (ErrandQuery q [r], KnownNat n) => RowParser n r -> q r -> ErrandResult q [r]
- prepare :: PrepQuery a r -> Errand ()
- beginTransaction :: Errand ()
- commitTransaction :: Errand ()
- saveTransaction :: ByteString -> Errand ()
- rollbackTransaction :: Errand ()
- rollbackTransactionTo :: ByteString -> Errand ()
- withTransaction :: Errand a -> Errand ()
- data Query a = Query {
- queryStatement :: ByteString
- queryParams :: [Maybe (Oid, ByteString, Format)]
- data PrepQuery ts a = PrepQuery {
- prepName :: ByteString
- prepStatement :: ByteString
- prepOids :: [Oid]
- prepParams :: Tuple ts -> [Maybe (ByteString, Format)]
- pgQuery :: QuasiQuoter
- pgPrepQuery :: QuasiQuoter
- pgQueryGen :: QuasiQuoter
- newtype Oid :: * = Oid CUInt
- class KnownNat (Width a) => Entity a where
- data Table = Table {
- tableName :: ByteString
- tableCols :: [ByteString]
- class Entity a => TableEntity a where
- data ErrandError
- data ErrorCode
- data ExecStatus :: *
- data RowError = RowError RowErrorLocation RowErrorDetail
- data RowErrorLocation = RowErrorLocation Column Row
- data RowErrorDetail
Errand
An interaction with the database
runErrand :: Connection -> Errand a -> IO (Either ErrandError a) Source #
Run an errand.
execute :: ErrandQuery q Result => q r -> ErrandResult q Result Source #
Execute the query and return its internal result.
execute' :: ErrandQuery q Int => q r -> ErrandResult q Int Source #
query :: (Entity r, ErrandQuery q [r]) => q r -> ErrandResult q [r] Source #
Execute a query and process its result set.
queryWith :: (ErrandQuery q [r], KnownNat n) => RowParser n r -> q r -> ErrandResult q [r] Source #
Execute a query and process its result set using the provided RowParser
.
beginTransaction :: Errand () Source #
Begin a transaction.
commitTransaction :: Errand () Source #
Commit transaction.
saveTransaction :: ByteString -> Errand () Source #
Create savepoint within transaction.
rollbackTransaction :: Errand () Source #
Roll back transaction.
rollbackTransactionTo :: ByteString -> Errand () Source #
Roll back to a specific savepoint.
withTransaction :: Errand a -> Errand () Source #
Do something within a transaction.
Query
Query object
Query | |
|
Preparable query object
PrepQuery | |
|
pgQuery :: QuasiQuoter Source #
Generate a Query. This utilizes an intermediate query generator of type QueryGenerator ()
.
See Database.PostgreSQL.Store.Query.TH for detailed description of the language accepted by this quasi quoter.
pgPrepQuery :: QuasiQuoter Source #
Generate a PrepQuery. The intermediate query generator has type QueryGenerator (Tuple ts)
where ts
has kind [Type]
. ts
represents the types of the parameters to this prepared query.
It is highly recommended that supply a type signature, if you give the resulting expression a name, to avoid ambiguity.
q :: PrepQuery '[Int, String] User q = [pgPrepQuery| SELECT #User(u) FROM @User u WHERE age < $(param0) AND name LIKE $(param1) |]
See Database.PostgreSQL.Store.Query.TH for detailed description of the language accepted by this quasi quoter.
pgQueryGen :: QuasiQuoter Source #
Generate a QueryGenerator
expression.
See Database.PostgreSQL.Store.Query.TH for detailed description of the language accepted by this quasi quoter.
Types
Entity
class KnownNat (Width a) => Entity a where Source #
An entity that is used as a parameter or result of a query.
genEntity :: QueryGenerator a Source #
Embed the entity into the query.
genEntity :: (Generic a, GEntity (Rep a)) => QueryGenerator a Source #
Embed the entity into the query.
parseEntity :: RowParser (Width a) a Source #
Retrieve an instance of a
from the result set.
parseEntity :: (Generic a, GEntity (Rep a), Width a ~ GEntityWidth (Rep a)) => RowParser (Width a) a Source #
Retrieve an instance of a
from the result set.
Entity Bool Source # | boolean |
Entity Double Source # | Any floating-point number |
Entity Float Source # | Any floating-point number |
Entity Int Source # | Any integer |
Entity Int8 Source # | Any integer |
Entity Int16 Source # | Any integer |
Entity Int32 Source # | Any integer |
Entity Int64 Source # | Any integer |
Entity Integer Source # | Any integer |
Entity Word Source # | Any unsigned integer |
Entity Word8 Source # | Any unsigned integer |
Entity Word16 Source # | Any unsigned integer |
Entity Word32 Source # | Any unsigned integer |
Entity Word64 Source # | Any unsigned integer |
Entity ByteString Source # |
|
Entity ByteString Source # |
|
Entity Scientific Source # | Any numeric type |
Entity String Source # |
|
Entity Text Source # |
|
Entity Value Source # |
|
Entity Text Source # |
|
Entity Natural Source # | Any unsigned integer |
Entity a => Entity (Maybe a) Source # | A value which may be |
GenericEntity (a, b) => Entity (a, b) Source # | Chain of 2 entities |
GenericEntity (a, b, c) => Entity (a, b, c) Source # | Chain of 3 entities |
GenericEntity (a, b, c, d) => Entity (a, b, c, d) Source # | Chain of 4 entities |
GenericEntity (a, b, c, d, e) => Entity (a, b, c, d, e) Source # | Chain of 5 entities |
GenericEntity (a, b, c, d, e, f) => Entity (a, b, c, d, e, f) Source # | Chain of 6 entities |
GenericEntity (a, b, c, d, e, f, g) => Entity (a, b, c, d, e, f, g) Source # | Chain of 7 entities |
Tables
Description of a table
Table | |
|
class Entity a => TableEntity a where Source #
Table entity with extra information about its name and column names
describeTableType :: Tagged a Table Source #
Describe the table type.
describeTableType :: GenericTable a => Tagged a Table Source #
Describe the table type.
Errors
data ErrandError Source #
Error during errand
NoResult | No |
UserError String | A user has thrown an error. |
ExecError ExecStatus ErrorCode ByteString ByteString ByteString | Query execution failed. |
ParseError RowError | Result processing failed. |
Error codes
data ExecStatus :: * #
EmptyQuery | The string sent to the server was empty. |
CommandOk | Successful completion of a command returning no data. |
TuplesOk | Successful completion of a command returning data (such as a SELECT or SHOW). |
CopyOut | Copy Out (from server) data transfer started. |
CopyIn | Copy In (to server) data transfer started. |
CopyBoth | Copy In/Out data transfer started. |
BadResponse | The server's response was not understood. |
NonfatalError | A nonfatal error (a notice or warning) occurred. |
FatalError | A fatal error occurred. |
SingleTuple | The PGresult contains a single result tuple from the current command. This status occurs only when single-row mode has been selected for the query. |
An error that occured when parsing a row
data RowErrorLocation Source #
Location of an error
data RowErrorDetail Source #
Errors that occur during row parsing
TooFewColumns | Underlying |
ColumnRejected | A column value could not be parsed. |