postgresql-query-3.7.0: Sql interpolating quasiquote plus some kind of primitive ORM using it

Safe HaskellNone
LanguageHaskell2010

Database.PostgreSQL.Query

Contents

Synopsis

Common usage modules

Some re-exports from postgresql-simple

data Connection #

Instances
Eq Connection 
Instance details

Defined in Database.PostgreSQL.Simple.Internal

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 https://www.postgresql.org/docs/9.5/static/libpq-connect.html#LIBPQ-CONNSTRING for more information. Also note that environment variables also affect parameters not provided, parameters provided as the empty string, and a few other things; see https://www.postgresql.org/docs/9.5/static/libpq-envars.html for details. 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. The path of the pgpass file may be specified by setting the PGPASSFILE environment variable. See https://www.postgresql.org/docs/9.5/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 https://www.postgresql.org/docs/9.5/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 connection parameters. In particular, sslmode needs to be set to require, verify-ca, or verify-full in order to perform certificate validation. When sslmode is require, then you will also need to specify 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. See https://www.postgresql.org/docs/9.5/static/libpq-ssl.html for detailed information regarding libpq and SSL.

data ConnectInfo #

Instances
Eq ConnectInfo 
Instance details

Defined in Database.PostgreSQL.Simple.Internal

Read ConnectInfo 
Instance details

Defined in Database.PostgreSQL.Simple.Internal

Show ConnectInfo 
Instance details

Defined in Database.PostgreSQL.Simple.Internal

Generic ConnectInfo 
Instance details

Defined in Database.PostgreSQL.Simple.Internal

Associated Types

type Rep ConnectInfo :: Type -> Type #

type Rep ConnectInfo 
Instance details

Defined in Database.PostgreSQL.Simple.Internal

type Rep ConnectInfo = D1 (MetaData "ConnectInfo" "Database.PostgreSQL.Simple.Internal" "postgresql-simple-0.6.2-HrAesFeJ1Q88BOFdkhYIHC" False) (C1 (MetaCons "ConnectInfo" PrefixI True) ((S1 (MetaSel (Just "connectHost") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "connectPort") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word16)) :*: (S1 (MetaSel (Just "connectUser") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: (S1 (MetaSel (Just "connectPassword") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "connectDatabase") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))))

class ToField a where #

A type that may be used as a single parameter to a SQL query.

Methods

toField :: a -> Action #

Prepare a value for substitution into a query string.

Instances
ToField Bool 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Bool -> Action #

ToField Double 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Double -> Action #

ToField Float 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Float -> Action #

ToField Int 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Int -> Action #

ToField Int8 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Int8 -> Action #

ToField Int16 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Int16 -> Action #

ToField Int32 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Int32 -> Action #

ToField Int64 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Int64 -> Action #

ToField Integer 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Integer -> Action #

ToField Word 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Word -> Action #

ToField Word8 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Word8 -> Action #

ToField Word16 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Word16 -> Action #

ToField Word32 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Word32 -> Action #

ToField Word64 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Word64 -> Action #

ToField ByteString 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: ByteString -> Action #

ToField ByteString 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: ByteString -> Action #

ToField Scientific 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Scientific -> Action #

ToField Text 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Text -> Action #

ToField UTCTime 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: UTCTime -> Action #

ToField Value 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Value -> Action #

ToField Text 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Text -> Action #

ToField Oid 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Oid -> Action #

ToField HStoreBuilder 
Instance details

Defined in Database.PostgreSQL.Simple.HStore.Implementation

ToField HStoreList 
Instance details

Defined in Database.PostgreSQL.Simple.HStore.Implementation

Methods

toField :: HStoreList -> Action #

ToField HStoreMap 
Instance details

Defined in Database.PostgreSQL.Simple.HStore.Implementation

Methods

toField :: HStoreMap -> Action #

ToField Action 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Action -> Action #

ToField Null 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Null -> Action #

ToField Default 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Default -> Action #

ToField Identifier 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Identifier -> Action #

ToField QualifiedIdentifier 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

ToField LocalTimestamp 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

ToField UTCTimestamp 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

ToField ZonedTimestamp 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

ToField Date 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Date -> Action #

ToField ZonedTime 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: ZonedTime -> Action #

ToField LocalTime 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: LocalTime -> Action #

ToField TimeOfDay 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: TimeOfDay -> Action #

ToField NominalDiffTime 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

ToField Day 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Day -> Action #

ToField UUID 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: UUID -> Action #

ToField InetText Source # 
Instance details

Defined in Database.PostgreSQL.Query.Types

Methods

toField :: InetText -> Action #

ToField [Char] 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: [Char] -> Action #

ToField a => ToField (Maybe a) 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Maybe a -> Action #

ToField (CI Text)

citext

Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: CI Text -> Action #

ToField (CI Text)

citext

Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: CI Text -> Action #

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

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: In [a] -> Action #

ToField (Binary ByteString) 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

ToField (Binary ByteString) 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

ToField a => ToField (PGArray a) 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: PGArray a -> Action #

ToRow a => ToField (Values a) 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Values a -> Action #

ToField a => ToField (Vector a) 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Vector a -> Action #

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.

You can derive ToRow for your data type using GHC generics, like this:

{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric  #-}

import GHC.Generics (Generic)
import Database.PostgreSQL.Simple (ToRow)

data User = User { name :: String, fileQuota :: Int }
  deriving (Generic, ToRow)

Note that this only works for product types (e.g. records) and does not support sum types or recursive types.

Minimal complete definition

Nothing

Methods

toRow :: a -> [Action] #

Instances
ToRow () 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: () -> [Action] #

ToField a => ToRow [a] 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

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

ToField a => ToRow (Only a) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: Only a -> [Action] #

(ToField a, ToField b) => ToRow (a, b) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

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

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

Defined in Database.PostgreSQL.Simple.ToRow

Methods

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

(ToField a, ToField b, ToField c) => ToRow (a, b, c) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c) -> [Action] #

(ToField a, ToField b, ToField c, ToField d) => ToRow (a, b, c, d) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d) -> [Action] #

(ToField a, ToField b, ToField c, ToField d, ToField e) => ToRow (a, b, c, d, e) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e) -> [Action] #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f) => ToRow (a, b, c, d, e, f) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f) -> [Action] #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g) => ToRow (a, b, c, d, e, f, g) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f, g) -> [Action] #

(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) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f, g, h) -> [Action] #

(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) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f, g, h, i) -> [Action] #

(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) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f, g, h, i, j) -> [Action] #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i, ToField j, ToField k) => ToRow (a, b, c, d, e, f, g, h, i, j, k) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f, g, h, i, j, k) -> [Action] #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i, ToField j, ToField k, ToField l) => ToRow (a, b, c, d, e, f, g, h, i, j, k, l) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f, g, h, i, j, k, l) -> [Action] #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i, ToField j, ToField k, ToField l, ToField m) => ToRow (a, b, c, d, e, f, g, h, i, j, k, l, m) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> [Action] #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i, ToField j, ToField k, ToField l, ToField m, ToField n) => ToRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> [Action] #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i, ToField j, ToField k, ToField l, ToField m, ToField n, ToField o) => ToRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> [Action] #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i, ToField j, ToField k, ToField l, ToField m, ToField n, ToField o, ToField p) => ToRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) -> [Action] #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i, ToField j, ToField k, ToField l, ToField m, ToField n, ToField o, ToField p, ToField q) => ToRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) -> [Action] #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i, ToField j, ToField k, ToField l, ToField m, ToField n, ToField o, ToField p, ToField q, ToField r) => ToRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) -> [Action] #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i, ToField j, ToField k, ToField l, ToField m, ToField n, ToField o, ToField p, ToField q, ToField r, ToField s) => ToRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) -> [Action] #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i, ToField j, ToField k, ToField l, ToField m, ToField n, ToField o, ToField p, ToField q, ToField r, ToField s, ToField t) => ToRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) -> [Action] #

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.Result to be retained. Thus, implementations of fromField 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.Result before it has been passed to fromField. This is because for short strings, it's cheaper to copy the string than to set up a finalizer.

Instances
FromField Bool

bool

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Char

"char", bpchar

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Double

int2, int4, float4, float8 (Uses attoparsec's double routine, for better accuracy convert to Scientific or Rational first)

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Float

int2, float4 (Uses attoparsec's double routine, for better accuracy convert to Scientific or Rational first)

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Int

int2, int4, and if compiled as 64-bit code, int8 as well. This library was compiled as 64-bit code.

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Int16

int2

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Int32

int2, int4

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Int64

int2, int4, int8

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Integer

int2, int4, int8

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField ()

void

Instance details

Defined in Database.PostgreSQL.Simple.FromField

Methods

fromField :: FieldParser () #

FromField ByteString

bytea, name, text, "char", bpchar, varchar, unknown

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField ByteString

bytea, name, text, "char", bpchar, varchar, unknown

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Scientific

int2, int4, int8, float4, float8, numeric

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Text

name, text, "char", bpchar, varchar

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField UTCTime

timestamptz

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Value

json, jsonb

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Text

name, text, "char", bpchar, varchar

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Oid

oid

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField HStoreList

hstore

Instance details

Defined in Database.PostgreSQL.Simple.HStore.Implementation

FromField HStoreMap 
Instance details

Defined in Database.PostgreSQL.Simple.HStore.Implementation

FromField Null

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

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField LocalTimestamp

timestamp

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField UTCTimestamp

timestamptz

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField ZonedTimestamp

timestamptz

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Date

date

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField ZonedTime

timestamptz

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField LocalTime

timestamp

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField TimeOfDay

time

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Day

date

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField UUID

uuid

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField InetText Source # 
Instance details

Defined in Database.PostgreSQL.Query.Types

FromField [Char]

name, text, "char", bpchar, varchar

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField a => FromField (Maybe a)

For dealing with null values. Compatible with any postgresql type compatible with type a. Note that the type is not checked if the value is null, although it is inadvisable to rely on this behavior.

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField (Ratio Integer)

int2, int4, int8, float4, float8, numeric

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField a => FromField (IORef a)

Compatible with the same set of types as a. Note that modifying the IORef does not have any effects outside the local process on the local machine.

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField a => FromField (MVar a)

Compatible with the same set of types as a. Note that modifying the MVar does not have any effects outside the local process on the local machine.

Instance details

Defined in Database.PostgreSQL.Simple.FromField

Methods

fromField :: FieldParser (MVar a) #

FromField (CI Text)

citext

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField (CI Text)

citext

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField (Binary ByteString)

bytea

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField (Binary ByteString)

bytea

Instance details

Defined in Database.PostgreSQL.Simple.FromField

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

any postgresql array whose elements are compatible with type a

Instance details

Defined in Database.PostgreSQL.Simple.FromField

(FromField a, Typeable a) => FromField (Vector a) 
Instance details

Defined in Database.PostgreSQL.Simple.FromField

(FromField a, Typeable a) => FromField (IOVector a) 
Instance details

Defined in Database.PostgreSQL.Simple.FromField

(FromField a, FromField b) => FromField (Either a b)

Compatible with both types. Conversions to type b are preferred, the conversion to type a will be tried after the Right conversion fails.

Instance details

Defined in Database.PostgreSQL.Simple.FromField

Methods

fromField :: FieldParser (Either a b) #

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.

You can also derive FromRow for your data type using GHC generics, like this:

{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric  #-}

import GHC.Generics (Generic)
import Database.PostgreSQL.Simple (FromRow)

data User = User { name :: String, fileQuota :: Int }
  deriving (Generic, FromRow)

Note that this only works for product types (e.g. records) and does not support sum types or recursive types.

Note that field evaluates its 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.

Minimal complete definition

Nothing

Methods

fromRow :: RowParser a #

Instances
FromField a => FromRow [a] 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser [a] #

FromField a => FromRow (Maybe [a]) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe [a]) #

(FromField a, FromField b) => FromRow (Maybe (a, b)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b)) #

(FromField a, FromField b, FromField c) => FromRow (Maybe (a, b, c)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c)) #

(FromField a, FromField b, FromField c, FromField d) => FromRow (Maybe (a, b, c, d)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d)) #

(FromField a, FromField b, FromField c, FromField d, FromField e) => FromRow (Maybe (a, b, c, d, e)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f) => FromRow (Maybe (a, b, c, d, e, f)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g) => FromRow (Maybe (a, b, c, d, e, f, g)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h) => FromRow (Maybe (a, b, c, d, e, f, g, h)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g, h)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i) => FromRow (Maybe (a, b, c, d, e, f, g, h, i)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g, h, i)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j) => FromRow (Maybe (a, b, c, d, e, f, g, h, i, j)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g, h, i, j)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k) => FromRow (Maybe (a, b, c, d, e, f, g, h, i, j, k)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g, h, i, j, k)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l) => FromRow (Maybe (a, b, c, d, e, f, g, h, i, j, k, l)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g, h, i, j, k, l)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m) => FromRow (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n) => FromRow (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n, FromField o) => FromRow (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n, FromField o, FromField p) => FromRow (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n, FromField o, FromField p, FromField q) => FromRow (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n, FromField o, FromField p, FromField q, FromField r) => FromRow (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n, FromField o, FromField p, FromField q, FromField r, FromField s) => FromRow (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n, FromField o, FromField p, FromField q, FromField r, FromField s, FromField t) => FromRow (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t)) #

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

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (Only a)) #

FromField a => FromRow (Maybe (Vector a)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (Vector a)) #

FromField a => FromRow (Only a) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Only a) #

FromField a => FromRow (Vector a) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Vector a) #

(FromField a, FromField b) => FromRow (a, b) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b) #

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

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a :. b) #

(FromField a, FromField b, FromField c) => FromRow (a, b, c) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c) #

(FromField a, FromField b, FromField c, FromField d) => FromRow (a, b, c, d) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d) #

(FromField a, FromField b, FromField c, FromField d, FromField e) => FromRow (a, b, c, d, e) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f) => FromRow (a, b, c, d, e, f) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g) => FromRow (a, b, c, d, e, f, g) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f, g) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h) => FromRow (a, b, c, d, e, f, g, h) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f, g, h) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i) => FromRow (a, b, c, d, e, f, g, h, i) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f, g, h, i) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j) => FromRow (a, b, c, d, e, f, g, h, i, j) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f, g, h, i, j) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k) => FromRow (a, b, c, d, e, f, g, h, i, j, k) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f, g, h, i, j, k) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f, g, h, i, j, k, l) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l, m) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f, g, h, i, j, k, l, m) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f, g, h, i, j, k, l, m, n) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n, FromField o) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n, FromField o, FromField p) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n, FromField o, FromField p, FromField q) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n, FromField o, FromField p, FromField q, FromField r) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n, FromField o, FromField p, FromField q, FromField r, FromField s) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n, FromField o, FromField p, FromField q, FromField r, FromField s, FromField t) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) #

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

Defined in Database.PostgreSQL.Simple.Types

Methods

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

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

Ord Query 
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 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Show Query 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

showsPrec :: Int -> Query -> ShowS #

show :: Query -> String #

showList :: [Query] -> ShowS #

IsString Query 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

fromString :: String -> Query #

Semigroup Query 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

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

sconcat :: NonEmpty Query -> Query #

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

Monoid Query 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

mempty :: Query #

mappend :: Query -> Query -> Query #

mconcat :: [Query] -> Query #

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 -> () #

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

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (Only a)) #

FromField a => FromRow (Only a) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Only a) #

ToField a => ToRow (Only a) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: Only a -> [Action] #

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 #

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 
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) 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

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

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

Ord a => Ord (In a) 
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) 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Show a => Show (In a) 
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]) 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: In [a] -> Action #

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 () #

FromField Oid

oid

Instance details

Defined in Database.PostgreSQL.Simple.FromField

ToField Oid 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Oid -> Action #

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 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) 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

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

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

Ord a => Ord (Values a) 
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) 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Show a => Show (Values a) 
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) 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: Values a -> Action #

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

Defined in Database.PostgreSQL.Simple.Types

Methods

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

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

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

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

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a :. b) #

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

Defined in Database.PostgreSQL.Simple.ToRow

Methods

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

newtype PGArray a #

Wrap a list for use as a PostgreSQL array.

Constructors

PGArray 

Fields

Instances
Functor PGArray 
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) 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

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

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

Ord a => Ord (PGArray a) 
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) 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Show a => Show (PGArray a) 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

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

show :: PGArray a -> String #

showList :: [PGArray a] -> ShowS #

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

any postgresql array whose elements are compatible with type a

Instance details

Defined in Database.PostgreSQL.Simple.FromField

ToField a => ToField (PGArray a) 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: PGArray a -> Action #