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

Copyright(c) 2011 MailRank Inc.
(c) 2011-2012 Leon P Smith
LicenseBSD3
MaintainerLeon P Smith <leon@melding-monads.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Database.PostgreSQL.Simple.Types

Description

Basic types.

Synopsis

Documentation

data Null Source #

A placeholder for the SQL NULL value.

Constructors

Null 
Instances
Eq Null Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

(==) :: Null -> Null -> Bool #

(/=) :: Null -> Null -> Bool #

Read Null Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Show Null Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

showsPrec :: Int -> Null -> ShowS #

show :: Null -> String #

showList :: [Null] -> ShowS #

ToField Null Source # 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Null -> Action Source #

FromField Null Source #

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

Instance details

Defined in Database.PostgreSQL.Simple.FromField

data Default Source #

A placeholder for the PostgreSQL DEFAULT value.

Constructors

Default 

newtype Only a #

The 1-tuple type or single-value "collection".

This type is structurally equivalent to the Identity type, but its intent is more about serving as the anonymous 1-tuple type missing from Haskell for attaching typeclass instances.

Parameter usage example:

encodeSomething (Only (42::Int))

Result usage example:

xs <- decodeSomething
forM_ xs $ \(Only id) -> {- ... -}

Constructors

Only 

Fields

Instances
Functor Only 
Instance details

Defined in Data.Tuple.Only

Methods

fmap :: (a -> b) -> Only a -> Only b #

(<$) :: a -> Only b -> Only a #

Eq a => Eq (Only a) 
Instance details

Defined in Data.Tuple.Only

Methods

(==) :: Only a -> Only a -> Bool #

(/=) :: Only a -> Only a -> Bool #

Data a => Data (Only a) 
Instance details

Defined in Data.Tuple.Only

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Only a -> c (Only a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Only a) #

toConstr :: Only a -> Constr #

dataTypeOf :: Only a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Only a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Only a)) #

gmapT :: (forall b. Data b => b -> b) -> Only a -> Only a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Only a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Only a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Only a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Only a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Only a -> m (Only a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Only a -> m (Only a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Only a -> m (Only a) #

Ord a => Ord (Only a) 
Instance details

Defined in Data.Tuple.Only

Methods

compare :: Only a -> Only a -> Ordering #

(<) :: Only a -> Only a -> Bool #

(<=) :: Only a -> Only a -> Bool #

(>) :: Only a -> Only a -> Bool #

(>=) :: Only a -> Only a -> Bool #

max :: Only a -> Only a -> Only a #

min :: Only a -> Only a -> Only a #

Read a => Read (Only a) 
Instance details

Defined in Data.Tuple.Only

Show a => Show (Only a) 
Instance details

Defined in Data.Tuple.Only

Methods

showsPrec :: Int -> Only a -> ShowS #

show :: Only a -> String #

showList :: [Only a] -> ShowS #

Generic (Only a) 
Instance details

Defined in Data.Tuple.Only

Associated Types

type Rep (Only a) :: Type -> Type #

Methods

from :: Only a -> Rep (Only a) x #

to :: Rep (Only a) x -> Only a #

NFData a => NFData (Only a) 
Instance details

Defined in Data.Tuple.Only

Methods

rnf :: Only a -> () #

ToField a => ToRow (Only a) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: Only a -> [Action] Source #

FromField a => FromRow (Maybe (Only a)) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

FromField a => FromRow (Only a) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Only a) Source #

type Rep (Only a) 
Instance details

Defined in Data.Tuple.Only

type Rep (Only a) = D1 (MetaData "Only" "Data.Tuple.Only" "Only-0.1-4eYnxvcrr7tEbYgCvIkHLb" True) (C1 (MetaCons "Only" PrefixI True) (S1 (MetaSel (Just "fromOnly") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 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]))

Note that In [] expands to (null), which works as expected in the query above, but evaluates to the logical null value on every row instead of TRUE. This means that changing the query above to ... id NOT in ? and supplying the empty list as the parameter returns zero rows, instead of all of them as one would expect.

Since postgresql doesn't seem to provide a syntax for actually specifying an empty list, which could solve this completely, there are two workarounds particularly worth mentioning, namely:

  1. Use postgresql-simple's Values type instead, which can handle the empty case correctly. Note however that while specifying the postgresql type "int4" is mandatory in the empty case, specifying the haskell type Values (Only Int) would not normally be needed in realistic use cases.

    query c "select * from whatever where id not in ?"
            (Only (Values ["int4"] [] :: Values (Only Int)))
  2. Use sql's COALESCE operator to turn a logical null into the correct boolean. Note however that the correct boolean depends on the use case:

    query c "select * from whatever where coalesce(id NOT in ?, TRUE)"
            (Only (In [] :: In [Int]))
    query c "select * from whatever where coalesce(id IN ?, FALSE)"
            (Only (In [] :: In [Int]))

    Note that at as of PostgreSQL 9.4, the query planner cannot see inside the COALESCE operator, so if you have an index on id then you probably don't want to write the last example with COALESCE, which would result in a table scan. There are further caveats if id can be null or you want null treated sensibly as a component of IN or NOT IN.

Constructors

In a 
Instances
Functor In Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

fmap :: (a -> b) -> In a -> In b #

(<$) :: a -> In b -> In a #

Eq a => Eq (In a) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

(==) :: In a -> In a -> Bool #

(/=) :: In a -> In a -> Bool #

Ord a => Ord (In a) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

compare :: In a -> In a -> Ordering #

(<) :: In a -> In a -> Bool #

(<=) :: In a -> In a -> Bool #

(>) :: In a -> In a -> Bool #

(>=) :: In a -> In a -> Bool #

max :: In a -> In a -> In a #

min :: In a -> In a -> In a #

Read a => Read (In a) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Show a => Show (In a) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

showsPrec :: Int -> In a -> ShowS #

show :: In a -> String #

showList :: [In a] -> ShowS #

ToField a => ToField (In [a]) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: In [a] -> Action Source #

newtype Binary a Source #

Wrap binary data for use as a bytea value.

Constructors

Binary 

Fields

Instances
Functor Binary Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

fmap :: (a -> b) -> Binary a -> Binary b #

(<$) :: a -> Binary b -> Binary a #

Eq a => Eq (Binary a) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

(==) :: Binary a -> Binary a -> Bool #

(/=) :: Binary a -> Binary a -> Bool #

Ord a => Ord (Binary a) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

compare :: Binary a -> Binary a -> Ordering #

(<) :: Binary a -> Binary a -> Bool #

(<=) :: Binary a -> Binary a -> Bool #

(>) :: Binary a -> Binary a -> Bool #

(>=) :: Binary a -> Binary a -> Bool #

max :: Binary a -> Binary a -> Binary a #

min :: Binary a -> Binary a -> Binary a #

Read a => Read (Binary a) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Show a => Show (Binary a) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

showsPrec :: Int -> Binary a -> ShowS #

show :: Binary a -> String #

showList :: [Binary a] -> ShowS #

ToField (Binary ByteString) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

ToField (Binary ByteString) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

FromField (Binary ByteString) Source #

bytea

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField (Binary ByteString) Source #

bytea

Instance details

Defined in Database.PostgreSQL.Simple.FromField

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.

Instances
Eq QualifiedIdentifier Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Ord QualifiedIdentifier Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Read QualifiedIdentifier Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Show QualifiedIdentifier Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

IsString QualifiedIdentifier Source #

"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.

Instance details

Defined in Database.PostgreSQL.Simple.Types

Hashable QualifiedIdentifier Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

ToField QualifiedIdentifier Source # 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

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 
Instances
Eq Query Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

(==) :: Query -> Query -> Bool #

(/=) :: Query -> Query -> Bool #

Ord Query Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

compare :: Query -> Query -> Ordering #

(<) :: Query -> Query -> Bool #

(<=) :: Query -> Query -> Bool #

(>) :: Query -> Query -> Bool #

(>=) :: Query -> Query -> Bool #

max :: Query -> Query -> Query #

min :: Query -> Query -> Query #

Read Query Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Show Query Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

showsPrec :: Int -> Query -> ShowS #

show :: Query -> String #

showList :: [Query] -> ShowS #

IsString Query Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

fromString :: String -> Query #

Semigroup Query Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

(<>) :: Query -> Query -> Query #

sconcat :: NonEmpty Query -> Query #

stimes :: Integral b => b -> Query -> Query #

Monoid Query Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

mempty :: Query #

mappend :: Query -> Query -> Query #

mconcat :: [Query] -> Query #

newtype Oid #

Constructors

Oid CUInt 
Instances
Eq Oid 
Instance details

Defined in Database.PostgreSQL.LibPQ

Methods

(==) :: Oid -> Oid -> Bool #

(/=) :: Oid -> Oid -> Bool #

Ord Oid 
Instance details

Defined in Database.PostgreSQL.LibPQ

Methods

compare :: Oid -> Oid -> Ordering #

(<) :: Oid -> Oid -> Bool #

(<=) :: Oid -> Oid -> Bool #

(>) :: Oid -> Oid -> Bool #

(>=) :: Oid -> Oid -> Bool #

max :: Oid -> Oid -> Oid #

min :: Oid -> Oid -> Oid #

Read Oid 
Instance details

Defined in Database.PostgreSQL.LibPQ

Show Oid 
Instance details

Defined in Database.PostgreSQL.LibPQ

Methods

showsPrec :: Int -> Oid -> ShowS #

show :: Oid -> String #

showList :: [Oid] -> ShowS #

Storable Oid 
Instance details

Defined in Database.PostgreSQL.LibPQ

Methods

sizeOf :: Oid -> Int #

alignment :: Oid -> Int #

peekElemOff :: Ptr Oid -> Int -> IO Oid #

pokeElemOff :: Ptr Oid -> Int -> Oid -> IO () #

peekByteOff :: Ptr b -> Int -> IO Oid #

pokeByteOff :: Ptr b -> Int -> Oid -> IO () #

peek :: Ptr Oid -> IO Oid #

poke :: Ptr Oid -> Oid -> IO () #

ToField Oid Source # 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Oid -> Action Source #

FromField Oid Source #

oid

Instance details

Defined in Database.PostgreSQL.Simple.FromField

data h :. t infixr 3 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 infixr 3 
Instances
(Eq h, Eq t) => Eq (h :. t) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

(==) :: (h :. t) -> (h :. t) -> Bool #

(/=) :: (h :. t) -> (h :. t) -> Bool #

(Ord h, Ord t) => Ord (h :. t) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

compare :: (h :. t) -> (h :. t) -> Ordering #

(<) :: (h :. t) -> (h :. t) -> Bool #

(<=) :: (h :. t) -> (h :. t) -> Bool #

(>) :: (h :. t) -> (h :. t) -> Bool #

(>=) :: (h :. t) -> (h :. t) -> Bool #

max :: (h :. t) -> (h :. t) -> h :. t #

min :: (h :. t) -> (h :. t) -> h :. t #

(Read h, Read t) => Read (h :. t) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

readsPrec :: Int -> ReadS (h :. t) #

readList :: ReadS [h :. t] #

readPrec :: ReadPrec (h :. t) #

readListPrec :: ReadPrec [h :. t] #

(Show h, Show t) => Show (h :. t) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

showsPrec :: Int -> (h :. t) -> ShowS #

show :: (h :. t) -> String #

showList :: [h :. t] -> ShowS #

(ToRow a, ToRow b) => ToRow (a :. b) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a :. b) -> [Action] Source #

(FromRow a, FromRow b) => FromRow (a :. b) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a :. b) Source #

newtype PGArray a Source #

Wrap a list for use as a PostgreSQL array.

Constructors

PGArray 

Fields

Instances
Functor PGArray Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

fmap :: (a -> b) -> PGArray a -> PGArray b #

(<$) :: a -> PGArray b -> PGArray a #

Eq a => Eq (PGArray a) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

(==) :: PGArray a -> PGArray a -> Bool #

(/=) :: PGArray a -> PGArray a -> Bool #

Ord a => Ord (PGArray a) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

compare :: PGArray a -> PGArray a -> Ordering #

(<) :: PGArray a -> PGArray a -> Bool #

(<=) :: PGArray a -> PGArray a -> Bool #

(>) :: PGArray a -> PGArray a -> Bool #

(>=) :: PGArray a -> PGArray a -> Bool #

max :: PGArray a -> PGArray a -> PGArray a #

min :: PGArray a -> PGArray a -> PGArray a #

Read a => Read (PGArray a) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Show a => Show (PGArray a) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

showsPrec :: Int -> PGArray a -> ShowS #

show :: PGArray a -> String #

showList :: [PGArray a] -> ShowS #

ToField a => ToField (PGArray a) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: PGArray a -> Action Source #

(FromField a, Typeable a) => FromField (PGArray a) Source #

any postgresql array whose elements are compatible with type a

Instance details

Defined in Database.PostgreSQL.Simple.FromField

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 ON TRUE
    ) 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 or serial, _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 https://www.postgresql.org/docs/9.5/static/sql-values.html for more information.

Constructors

Values [QualifiedIdentifier] [a] 
Instances
Eq a => Eq (Values a) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

(==) :: Values a -> Values a -> Bool #

(/=) :: Values a -> Values a -> Bool #

Ord a => Ord (Values a) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

compare :: Values a -> Values a -> Ordering #

(<) :: Values a -> Values a -> Bool #

(<=) :: Values a -> Values a -> Bool #

(>) :: Values a -> Values a -> Bool #

(>=) :: Values a -> Values a -> Bool #

max :: Values a -> Values a -> Values a #

min :: Values a -> Values a -> Values a #

Read a => Read (Values a) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Show a => Show (Values a) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

showsPrec :: Int -> Values a -> ShowS #

show :: Values a -> String #

showList :: [Values a] -> ShowS #

ToRow a => ToField (Values a) Source # 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Values a -> Action Source #