| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Database.PostgreSQL.Query
- module Database.PostgreSQL.Query.Entity
 - module Database.PostgreSQL.Query.Functions
 - module Database.PostgreSQL.Query.SqlBuilder
 - module Database.PostgreSQL.Query.TH
 - module Database.PostgreSQL.Query.Types
 - data Connection :: *
 - connect :: ConnectInfo -> IO Connection
 - defaultConnectInfo :: ConnectInfo
 - connectPostgreSQL :: ByteString -> IO Connection
 - data ConnectInfo :: * = ConnectInfo {}
 - class ToField a where
 - class ToRow a where
 - class FromField a where
- fromField :: FieldParser a
 
 - class FromRow a where
 - newtype Query :: * = Query {}
 - newtype Only a :: * -> * = Only {
- fromOnly :: a
 
 - newtype In a :: * -> * = In a
 - newtype Oid :: * = Oid CUInt
 - data Values a :: * -> * = Values [QualifiedIdentifier] [a]
 - data h :. t :: * -> * -> * = h :. t
 - newtype PGArray a :: * -> * = PGArray {
- fromPGArray :: [a]
 
 - newtype HStoreList :: * = HStoreList {
- fromHStoreList :: [(Text, Text)]
 
 - newtype HStoreMap :: * = HStoreMap {
- fromHStoreMap :: Map Text Text
 
 - class ToHStore a where
- toHStore :: a -> HStoreBuilder
 
 - data HStoreBuilder :: *
 - hstore :: (ToHStoreText a, ToHStoreText b) => a -> b -> HStoreBuilder
 - parseHStoreList :: ByteString -> Either String HStoreList
 - class ToHStoreText a where
- toHStoreText :: a -> HStoreText
 
 - data HStoreText :: *
 - sqlQQ :: QuasiQuoter
 
Common usage modules
module Database.PostgreSQL.Query.TH
Some re-exports from postgresql-simple
data Connection :: *
connect :: ConnectInfo -> IO Connection
Connect with the given username to the given database. Will throw an exception if it cannot connect.
defaultConnectInfo :: ConnectInfo
Default information for setting up a connection.
Defaults are as follows:
- Server on 
localhost - Port on 
5432 - User 
postgres - No password
 - Database 
postgres 
Use as in the following example:
connect defaultConnectInfo { connectHost = "db.example.com" }connectPostgreSQL :: ByteString -> IO Connection
Attempt to make a connection based on a libpq connection string. See http://www.postgresql.org/docs/9.3/static/libpq-connect.html#LIBPQ-CONNSTRING for more information. Here is an example with some of the most commonly used parameters:
host='db.somedomain.com' port=5432 ...
This attempts to connect to db.somedomain.com:5432.  Omitting the port
   will normally default to 5432.
On systems that provide unix domain sockets,  omitting the host parameter
   will cause libpq to attempt to connect via unix domain sockets.
   The default filesystem path to the socket is constructed from the
   port number and the DEFAULT_PGSOCKET_DIR constant defined in the
   pg_config_manual.h header file.  Connecting via unix sockets tends
   to use the peer authentication method, which is very secure and
   does not require a password.
On Windows and other systems without unix domain sockets, omitting
   the host will default to localhost.
... dbname='postgres' user='postgres' password='secret \' \\ pw'
This attempts to connect to a database named postgres with
   user postgres and password secret ' \ pw.  Backslash
   characters will have to be double-quoted in literal Haskell strings,
   of course.  Omitting dbname and user will both default to the
   system username that the client process is running as.
Omitting password will default to an appropriate password found
   in the pgpass file,  or no password at all if a matching line is
   not found.   See
   http://www.postgresql.org/docs/9.3/static/libpq-pgpass.html for
   more information regarding this file.
As all parameters are optional and the defaults are sensible, the empty connection string can be useful for development and exploratory use, assuming your system is set up appropriately.
On Unix, such a setup would typically consist of a local postgresql server listening on port 5432, as well as a system user, database user, and database sharing a common name, with permissions granted to the user on the database.
On Windows,  in addition you will either need pg_hba.conf
   to specify the use of the trust authentication method for
   the connection,  which may not be appropriate for multiuser
   or production machines, or you will need to use a pgpass file
   with the password or md5 authentication methods.
See http://www.postgresql.org/docs/9.3/static/client-authentication.html for more information regarding the authentication process.
SSL/TLS will typically "just work" if your postgresql server supports or
   requires it.  However,  note that libpq is trivially vulnerable to a MITM
   attack without setting additional SSL parameters in the connection string.
   In particular,  sslmode needs to set be require, verify-ca, or
   verify-full to perform certificate validation.   When sslmode is
   require,  then you will also need to have a sslrootcert file,
   otherwise no validation of the server's identity will be performed.
   Client authentication via certificates is also possible via the
   sslcert and sslkey parameters.
data ConnectInfo :: *
Constructors
| ConnectInfo | |
Fields 
  | |
Instances
class ToField a where
A type that may be used as a single parameter to a SQL query.
Instances
class ToRow a where
A collection type that can be turned into a list of rendering
 Actions.
Instances should use the toField method of the ToField class
 to perform conversion of each element of the collection.
Instances
| ToRow () | |
| ToField a => ToRow [a] | |
| ToField a => ToRow (Only a) | |
| (ToField a, ToField b) => ToRow (a, b) | |
| (ToRow a, ToRow b) => ToRow ((:.) a b) | |
| (ToField a, ToField b, ToField c) => ToRow (a, b, c) | |
| (ToField a, ToField b, ToField c, ToField d) => ToRow (a, b, c, d) | |
| (ToField a, ToField b, ToField c, ToField d, ToField e) => ToRow (a, b, c, d, e) | |
| (ToField a, ToField b, ToField c, ToField d, ToField e, ToField f) => ToRow (a, b, c, d, e, f) | |
| (ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g) => ToRow (a, b, c, d, e, f, g) | |
| (ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h) => ToRow (a, b, c, d, e, f, g, h) | |
| (ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i) => ToRow (a, b, c, d, e, f, g, h, i) | |
| (ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i, ToField j) => ToRow (a, b, c, d, e, f, g, h, i, j) | 
class FromField a where
A type that may be converted from a SQL type.
Methods
fromField :: FieldParser a
Convert a SQL value to a Haskell value.
Returns a list of exceptions if the conversion fails.  In the case of
 library instances,  this will usually be a single ResultError,  but
 may be a UnicodeException.
Note that retaining any reference to the Field argument causes
 the entire LibPQ. to be retained.  Thus, implementations
 of ResultfromField should return results that do not refer to this value
 after the result have been evaluated to WHNF.
Note that as of postgresql-simple-0.4.0.0,  the ByteString value
 has already been copied out of the LibPQ. before it has
 been passed to ResultfromField.  This is because for short strings, it's
 cheaper to copy the string than to set up a finalizer.
Instances
| FromField Bool | bool  | 
| FromField Char | "char"  | 
| FromField Double | int2, int4, float4, float8  (Uses attoparsec's   | 
| FromField Float | int2, float4    (Uses attoparsec's   | 
| FromField Int | int2, int4, and if compiled as 64-bit code, int8 as well. This library was compiled as 64-bit code.  | 
| FromField Int16 | int2  | 
| FromField Int32 | int2, int4  | 
| FromField Int64 | int2, int4, int8  | 
| FromField Integer | int2, int4, int8  | 
| FromField () | void  | 
| FromField ByteString | bytea, name, text, "char", bpchar, varchar, unknown  | 
| FromField ByteString | bytea, name, text, "char", bpchar, varchar, unknown  | 
| FromField Scientific | int2, int4, float4, float8, numeric  | 
| FromField Text | name, text, "char", bpchar, varchar  | 
| FromField UTCTime | timestamptz  | 
| FromField Value | json  | 
| FromField Text | name, text, "char", bpchar, varchar  | 
| FromField Oid | oid  | 
| FromField HStoreList | hstore  | 
| FromField HStoreMap | |
| FromField Null | compatible with any data type, but the value must be null  | 
| FromField LocalTimestamp | timestamp  | 
| FromField UTCTimestamp | timestamptz  | 
| FromField ZonedTimestamp | timestamptz  | 
| FromField Date | date  | 
| FromField LocalTime | timestamp  | 
| FromField ZonedTime | timestamptz  | 
| FromField TimeOfDay | time  | 
| FromField Day | date  | 
| FromField UUID | uuid  | 
| FromField InetText | |
| FromField [Char] | name, text, "char", bpchar, varchar  | 
| FromField (Ratio Integer) | int2, int4, float4, float8, numeric  | 
| FromField a => FromField (Maybe a) | For dealing with null values.  Compatible with any postgresql type
   compatible with type   | 
| FromField a => FromField (MVar a) | Compatible with the same set of types as   | 
| FromField a => FromField (IORef a) | Compatible with the same set of types as   | 
| FromField (CI Text) | citext  | 
| FromField (CI Text) | citext  | 
| FromField (Binary ByteString) | bytea  | 
| FromField (Binary ByteString) | bytea  | 
| (FromField a, Typeable * a) => FromField (PGArray a) | any postgresql array whose elements are compatible with type   | 
| (FromField a, Typeable * a) => FromField (Vector a) | |
| (FromField a, Typeable * a) => FromField (IOVector a) | |
| (FromField a, FromField b) => FromField (Either a b) | Compatible with both types.  Conversions to type   | 
class FromRow a where
A collection type that can be converted from a sequence of fields. Instances are provided for tuples up to 10 elements and lists of any length.
Note that instances can be defined outside of postgresql-simple, which is often useful. For example, here's an instance for a user-defined pair:
@data User = User { name :: String, fileQuota :: Int }
instance FromRow User where
     fromRow = User <$> field <*> field
 @
The number of calls to field must match the number of fields returned
 in a single row of the query result.  Otherwise,  a ConversionFailed
 exception will be thrown.
Note that field evaluates it's result to WHNF, so the caveats listed in
 mysql-simple and very early versions of postgresql-simple no longer apply.
 Instead, look at the caveats associated with user-defined implementations
 of fromField.
Instances
newtype Query :: *
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 Only a :: * -> *
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) -> {- ... -}newtype In a :: * -> *
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 | 
newtype Oid :: *
data Values a :: * -> *
Represents a VALUES table literal,  usable as an alternative
   to executeMany and returning.  The main advantage is that
   you can parametrize more than just a single VALUES expression.
   For example,  here's a query to insert a thing into one table
   and some attributes of that thing into another,   returning the
   new id generated by the database:
query c [sql|
    WITH new_thing AS (
      INSERT INTO thing (name) VALUES (?) RETURNING id
    ), new_attributes AS (
      INSERT INTO thing_attributes
         SELECT new_thing.id, attrs.*
           FROM new_thing JOIN ? attrs
    ) SELECT * FROM new_thing
 |] ("foo", Values [  "int4", "text"    ]
                   [ ( 1    , "hello" )
                   , ( 2    , "world" ) ])(Note this example uses writable common table expressions, which were added in PostgreSQL 9.1)
The second parameter gets expanded into the following SQL syntax:
(VALUES (1::"int4",'hello'::"text"),(2,'world'))
When the list of attributes is empty, the second parameter expands to:
(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.
   This behavior is usually correct given their intended use cases,
   but would certainly be wrong in the example above.
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 the first
   condition is not met,  postgresql-simple will throw an exception
   without issuing the query.   In the second case,  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] | 
data h :. t :: * -> * -> * infixr 3
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 infixr 3 | 
newtype PGArray a :: * -> *
Wrap a list for use as a PostgreSQL array.
Constructors
| PGArray | |
Fields 
  | |
data HStoreBuilder :: *
Represents valid hstore syntax.
hstore :: (ToHStoreText a, ToHStoreText b) => a -> b -> HStoreBuilder
class ToHStoreText a where
Methods
toHStoreText :: a -> HStoreText
Instances
| ToHStoreText ByteString | Assumed to be UTF-8 encoded  | 
| ToHStoreText ByteString | Assumed to be UTF-8 encoded  | 
| ToHStoreText Text | |
| ToHStoreText Text | |
| ToHStoreText HStoreText | 
Deprecated: Use sqlExp instead