Stability | experimental |
---|---|
Maintainer | Leon P Smith <[email protected]> |
Safe Haskell | None |
Database.PostgreSQL.Simple.Types
Description
Basic types.
- data Null = Null
- data Default = Default
- newtype Only a = Only {
- fromOnly :: a
- newtype In a = In a
- newtype Binary a = Binary {
- fromBinary :: a
- newtype Identifier = Identifier {}
- data QualifiedIdentifier = QualifiedIdentifier (Maybe ByteString) ByteString
- newtype Query = Query {}
- newtype Oid = Oid CUInt
- data h :. t = h :. t
- newtype Savepoint = Savepoint Query
- newtype PGArray a = PGArray {
- fromPGArray :: [a]
- data Values a = Values [QualifiedIdentifier] [a]
Documentation
A placeholder for the SQL NULL
value.
Constructors
Null |
A placeholder for the PostgreSQL DEFAULT
value.
Constructors
Default |
A single-value "collection".
This is useful if you need to supply a single parameter to a SQL query, or extract a single column from a SQL result.
Parameter example:
query c "select x from scores where x > ?" (Only
(42::Int))
Result example:
xs <- query_ c "select id from users"
forM_ xs $ \(Only
id) -> {- ... -}
Wrap a list of values for use in an IN
clause. Replaces a
single "?
" character with a parenthesized list of rendered
values.
Example:
query c "select * from whatever where id in ?" (Only (In [3,4,5]))
Constructors
In a |
Wrap binary data for use as a bytea
value.
Constructors
Binary | |
Fields
|
newtype Identifier Source
Wrap text for use as sql identifier, i.e. a table or column name.
Constructors
Identifier | |
Fields |
data QualifiedIdentifier Source
Wrap text for use as (maybe) qualified identifier, i.e. a table with schema, or column with table.
Constructors
QualifiedIdentifier (Maybe ByteString) ByteString |
A query string. This type is intended to make it difficult to construct a SQL query by concatenating string fragments, as that is an extremely common way to accidentally introduce SQL injection vulnerabilities into an application.
This type is an instance of IsString
, so the easiest way to
construct a query is to enable the OverloadedStrings
language
extension and then simply write the query in double quotes.
{-# LANGUAGE OverloadedStrings #-} import Database.PostgreSQL.Simple q :: Query q = "select ?"
The underlying type is a ByteString
, and literal Haskell strings
that contain Unicode characters will be correctly transformed to
UTF-8.
Constructors
Query | |
Fields |
newtype Oid
A composite type to parse your custom data structures without having to define dummy newtype wrappers every time.
instance FromRow MyData where ...
instance FromRow MyData2 where ...
then I can do the following for free:
res <- query' c ... forM res $ \(MyData{..} :. MyData2{..}) -> do ....
Constructors
h :. t |
Wrap a list for use as a PostgreSQL array.
Constructors
PGArray | |
Fields
|
Represents a VALUES
table literal, usable as an alternative
to executeMany
and returning
. For example:
execute c "INSERT INTO table (key,val) ?" (Only (Values ["int4","text"] [(1,"hello"),(2,"world")]))
Issues the following query:
INSERT INTO table (key,val) (VALUES (1::"int4",'hello'::"text"),(2,'world'))
When the list of values is empty, the following query will be issued:
INSERT INTO table (key,val) (VALUES (null::"int4",null::"text") LIMIT 0)
By contrast, executeMany
and returning
don't issue the query
in the empty case, and simply return 0
and []
respectively.
The advantage over executeMany
is in cases when you want to
parameterize table literals in addition to other parameters, as can
occur with writable common table expressions, for example.
The first argument is a list of postgresql type names. Because this
is turned into a properly quoted identifier, the type name is case
sensitive and must be as it appears in the pg_type
table. Thus,
you must write timestamptz
instead of timestamp with time zone
,
int4
instead of integer
, _int8
instead of bigint[]
, etcetera.
You may omit the type names, however, if you do so the list
of values must be non-empty, and postgresql must be able to infer
the types of the columns from the surrounding context. If these
conditions are not met, postgresql-simple will throw an exception
without issuing the query in the former case, and in the latter
the postgres server will return an error which will be turned into
a SqlError
exception.
See http://www.postgresql.org/docs/9.3/static/sql-values.html for more information.
Constructors
Values [QualifiedIdentifier] [a] |