postgresql-simple-0.4.4.1: Mid-Level PostgreSQL client library

Stabilityexperimental
MaintainerLeon P Smith <leon@melding-monads.com>
Safe HaskellNone

Database.PostgreSQL.Simple.Types

Description

Basic types.

Synopsis

Documentation

data Null Source

A placeholder for the SQL NULL value.

Constructors

Null 

Instances

Eq Null 
Read Null 
Show Null 
Typeable Null 
ToField Null 
FromField Null

compatible with any data type, but the value must be null

data Default Source

A placeholder for the PostgreSQL DEFAULT value.

Constructors

Default 

Instances

Read Default 
Show Default 
Typeable Default 
ToField Default 

newtype Only a Source

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) -> {- ... -}

Constructors

Only 

Fields

fromOnly :: a
 

Instances

Functor Only 
Typeable1 Only 
Eq a => Eq (Only a) 
Ord a => Ord (Only a) 
Read a => Read (Only a) 
Show a => Show (Only a) 
ToField a => ToRow (Only a) 
FromField a => FromRow (Maybe (Only a)) 
FromField a => FromRow (Only a) 

newtype In a Source

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 

Instances

Functor In 
Typeable1 In 
Eq a => Eq (In a) 
Ord a => Ord (In a) 
Read a => Read (In a) 
Show a => Show (In a) 
ToField a => ToField (In [a]) 

newtype Binary a Source

Wrap binary data for use as a bytea value.

Constructors

Binary 

Fields

fromBinary :: a
 

Instances

Functor Binary 
Typeable1 Binary 
Eq a => Eq (Binary a) 
Ord a => Ord (Binary a) 
Read a => Read (Binary a) 
Show a => Show (Binary a) 
ToField (Binary ByteString) 
ToField (Binary ByteString) 
FromField (Binary ByteString)

bytea

FromField (Binary ByteString)

bytea

newtype Identifier Source

Wrap text for use as sql identifier, i.e. a table or column name.

Constructors

Identifier 

Fields

fromIdentifier :: Text
 

data QualifiedIdentifier Source

Wrap text for use as (maybe) qualified identifier, i.e. a table with schema, or column with table.

Constructors

QualifiedIdentifier (Maybe Text) Text 

Instances

Eq QualifiedIdentifier 
Ord QualifiedIdentifier 
Read QualifiedIdentifier 
Show QualifiedIdentifier 
Typeable QualifiedIdentifier 
IsString QualifiedIdentifier

"foo.bar" will get turned into QualifiedIdentifier (Just "foo") "bar", while "foo" will get turned into QualifiedIdentifier Nothing "foo". Note this instance is for convenience, and does not match postgres syntax. It only examines the first period character, and thus cannot be used if the qualifying identifier contains a period for example.

Hashable QualifiedIdentifier 
ToField QualifiedIdentifier 

newtype Query Source

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

fromQuery :: ByteString
 

Instances

Eq Query 
Ord Query 
Read Query 
Show Query 
Typeable Query 
IsString Query 
Monoid Query 

newtype Oid

Constructors

Oid CUInt 

Instances

Eq Oid 
Ord Oid 
Read Oid 
Show Oid 
Storable Oid 
ToField Oid 
FromField Oid

oid

data h :. t Source

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 

Instances

Typeable2 :. 
(Eq h, Eq t) => Eq (:. h t) 
(Ord h, Ord t) => Ord (:. h t) 
(Read h, Read t) => Read (:. h t) 
(Show h, Show t) => Show (:. h t) 
(ToRow a, ToRow b) => ToRow (:. a b) 
(FromRow a, FromRow b) => FromRow (:. a b) 

newtype Savepoint Source

Constructors

Savepoint Query 

Instances

Eq Savepoint 
Ord Savepoint 
Read Savepoint 
Show Savepoint 
Typeable Savepoint 

newtype PGArray a Source

Wrap a list for use as a PostgreSQL array.

Constructors

PGArray 

Fields

fromPGArray :: [a]
 

Instances

Functor PGArray 
Typeable1 PGArray 
Eq a => Eq (PGArray a) 
Ord a => Ord (PGArray a) 
Read a => Read (PGArray a) 
Show a => Show (PGArray a) 
ToField a => ToField (PGArray a) 
(FromField a, Typeable a) => FromField (PGArray a)

any postgresql array whose elements are compatible with type a

data Values a Source

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] 

Instances

Typeable1 Values 
Eq a => Eq (Values a) 
Ord a => Ord (Values a) 
Read a => Read (Values a) 
Show a => Show (Values a) 
ToRow a => ToField (Values a)