-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Mid-Level PostgreSQL client library -- -- Mid-Level PostgreSQL client library, forked from mysql-simple. @package postgresql-simple @version 0.1 module Database.PostgreSQL.Simple.SqlQQ -- | sql is a quasiquoter that eases the syntactic burden of writing -- big sql statements in Haskell source code. For example: -- --
--   {-# LANGUAGE QuasiQuotes #-}
--   
--   query conn [sql| SELECT column_a, column_b
--                      FROM table1 NATURAL JOIN table2
--                     WHERE ? <= time AND time < ?
--                       AND name LIKE ?
--                     ORDER BY size DESC
--                     LIMIT 100                        |]
--              (beginTime,endTime,string)
--   
-- -- This quasiquoter attempts to mimimize whitespace; otherwise the above -- query would consist of approximately half whitespace when sent to the -- database backend. -- -- The implementation of the whitespace reducer is currently incomplete. -- Thus it can mess up your syntax in cases where whitespace should be -- preserved as-is. It does preserve whitespace inside standard SQL -- string literals. But it can get confused by the non-standard -- PostgreSQL string literal syntax (which is the default setting in -- PostgreSQL 8 and below), the extended escape string syntax, and other -- similar constructs. -- -- Of course, this caveat only applies to text written inside the SQL -- quasiquoter; whitespace reduction is a compile-time computation and -- thus will not touch the string parameter above, which is a -- run-time value. -- -- Also note that this will not work if the substring |] is -- contained in the query. sql :: QuasiQuoter -- | Basic types. module Database.PostgreSQL.Simple.Types -- | A placeholder for the SQL NULL value. data Null Null :: Null -- | 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 Only a Only :: a -> Only a fromOnly :: Only a -> 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 ?" (In [3,4,5])
--   
newtype In a In :: a -> In a -- | Wrap a mostly-binary string to be escaped in hexadecimal. newtype Binary a Binary :: a -> Binary a -- | 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. newtype Query Query :: ByteString -> Query fromQuery :: Query -> ByteString newtype Oid :: * Oid :: CUInt -> Oid -- | A composite type to parse your custom data structures without having -- to define dummy newtype wrappers every time. -- --
--   instance FromRow MyData where ...
--   
-- --
--   instance FromRow MyData2 where ...
--   
-- -- then I can do the following for free: -- --
--   res <- query' c ...
--   forM res $ \(MyData{..} :. MyData2{..}) -> do
--     ....
--   
data (:.) h t (:.) :: h -> t -> :. h t instance Typeable Null instance Typeable Query instance Typeable1 Only instance Typeable1 In instance Typeable1 Binary instance Typeable2 :. instance Read Null instance Show Null instance Eq Query instance Ord Query instance Eq a => Eq (Only a) instance Ord a => Ord (Only a) instance Read a => Read (Only a) instance Show a => Show (Only a) instance Functor Only instance Eq a => Eq (In a) instance Ord a => Ord (In a) instance Read a => Read (In a) instance Show a => Show (In a) instance Functor In instance Eq a => Eq (Binary a) instance Ord a => Ord (Binary a) instance Read a => Read (Binary a) instance Show a => Show (Binary a) instance Functor Binary instance (Eq h, Eq t) => Eq (h :. t) instance (Ord h, Ord t) => Ord (h :. t) instance (Show h, Show t) => Show (h :. t) instance (Read h, Read t) => Read (h :. t) instance Monoid Query instance IsString Query instance Read Query instance Show Query instance Eq Null -- | The ToField typeclass, for rendering a parameter to a SQL -- query. module Database.PostgreSQL.Simple.ToField -- | How to render an element when substituting it into a query. data Action -- | Render without escaping or quoting. Use for non-text types such as -- numbers, when you are certain that they will not introduce -- formatting vulnerabilities via use of characters such as spaces or -- "'". Plain :: Builder -> Action -- | Escape and enclose in quotes before substituting. Use for all -- text-like types, and anything else that may contain unsafe characters -- when rendered. Escape :: ByteString -> Action -- | Concatenate a series of rendering actions. Many :: [Action] -> Action -- | A type that may be used as a single parameter to a SQL query. class ToField a toField :: ToField a => a -> Action -- | Surround a string with single-quote characters: "'" -- -- This function does not perform any other escaping. inQuotes :: Builder -> Builder instance Typeable Action instance ToField TimeOfDay instance ToField Day instance ToField UTCTime instance ToField Text instance ToField [Char] instance ToField Text instance ToField ByteString instance ToField ByteString instance ToField Double instance ToField Float instance ToField Oid instance ToField Word64 instance ToField Word instance ToField Word32 instance ToField Word16 instance ToField Word8 instance ToField Integer instance ToField Int64 instance ToField Int instance ToField Int32 instance ToField Int16 instance ToField Int8 instance ToField Bool instance ToField Null instance ToField (Binary ByteString) instance ToField (Binary ByteString) instance ToField a => ToField (In [a]) instance ToField a => ToField (Maybe a) instance ToField Action instance Show Action -- | The QueryParams typeclass, for rendering a collection of -- parameters to a SQL query. -- -- Predefined instances are provided for tuples containing up to ten -- elements. module Database.PostgreSQL.Simple.ToRow -- | A collection type that can be turned into a list of rendering -- Actions. -- -- Instances should use the render method of the Param -- class to perform conversion of each element of the collection. class ToRow a toRow :: ToRow a => a -> [Action] instance ToField a => ToRow [a] instance (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 (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 (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 (ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g) => ToRow (a, b, c, d, e, f, g) instance (ToField a, ToField b, ToField c, ToField d, ToField e, ToField f) => ToRow (a, b, c, d, e, f) instance (ToField a, ToField b, ToField c, ToField d, ToField e) => ToRow (a, b, c, d, e) instance (ToField a, ToField b, ToField c, ToField d) => ToRow (a, b, c, d) instance (ToField a, ToField b, ToField c) => ToRow (a, b, c) instance (ToField a, ToField b) => ToRow (a, b) instance ToField a => ToRow (Only a) instance ToRow () module Database.PostgreSQL.Simple.Ok newtype ManyErrors ManyErrors :: [SomeException] -> ManyErrors data Ok a Errors :: [SomeException] -> Ok a Ok :: !a -> Ok a instance Typeable ManyErrors instance Typeable1 Ok instance Show ManyErrors instance Show a => Show (Ok a) instance Functor Ok instance Monad Ok instance MonadPlus Ok instance Alternative Ok instance Applicative Ok instance Eq a => Eq (Ok a) instance Exception ManyErrors module Database.PostgreSQL.Simple.BuiltinTypes data BuiltinType Bool :: BuiltinType Bytea :: BuiltinType Char :: BuiltinType Name :: BuiltinType Int8 :: BuiltinType Int2 :: BuiltinType Int4 :: BuiltinType Regproc :: BuiltinType Text :: BuiltinType Oid :: BuiltinType Tid :: BuiltinType Xid :: BuiltinType Cid :: BuiltinType Xml :: BuiltinType Point :: BuiltinType Lseg :: BuiltinType Path :: BuiltinType Box :: BuiltinType Polygon :: BuiltinType Line :: BuiltinType Cidr :: BuiltinType Float4 :: BuiltinType Float8 :: BuiltinType Abstime :: BuiltinType Reltime :: BuiltinType Tinterval :: BuiltinType Unknown :: BuiltinType Circle :: BuiltinType Money :: BuiltinType Macaddr :: BuiltinType Inet :: BuiltinType Bpchar :: BuiltinType Varchar :: BuiltinType Date :: BuiltinType Time :: BuiltinType Timestamp :: BuiltinType TimestampWithTimeZone :: BuiltinType Interval :: BuiltinType TimeWithTimeZone :: BuiltinType Bit :: BuiltinType Varbit :: BuiltinType Numeric :: BuiltinType Refcursor :: BuiltinType Record :: BuiltinType Void :: BuiltinType builtin2oid :: BuiltinType -> Oid oid2builtin :: Oid -> Maybe BuiltinType builtin2typname :: BuiltinType -> ByteString oid2typname :: Oid -> Maybe ByteString instance Typeable BuiltinType instance Eq BuiltinType instance Ord BuiltinType instance Enum BuiltinType instance Bounded BuiltinType instance Read BuiltinType instance Show BuiltinType -- | Internal bits. This interface is less stable and can change at any -- time. In particular this means that while the rest of the -- postgresql-simple package endeavors to follow the package versioning -- policy, this module does not. Also, at the moment there are things in -- here that aren't particularly internal and are exported elsewhere; -- these will eventually disappear from this module. module Database.PostgreSQL.Simple.Internal -- | A Field represents metadata about a particular field -- -- You don't particularly want to retain these structures for a long -- period of time, as they will retain the entire query result, not just -- the field metadata data Field Field :: !Result -> {-# UNPACK #-} !Column -> !ByteString -> Field result :: Field -> !Result column :: Field -> {-# UNPACK #-} !Column typename :: Field -> !ByteString name :: Field -> Maybe ByteString tableOid :: Field -> Oid tableColumn :: Field -> Int format :: Field -> Format typeOid :: Field -> Oid data Connection Connection :: {-# UNPACK #-} !MVar Connection -> {-# UNPACK #-} !MVar (IntMap ByteString) -> Connection connectionHandle :: Connection -> {-# UNPACK #-} !MVar Connection connectionObjects :: Connection -> {-# UNPACK #-} !MVar (IntMap ByteString) data SqlType Builtin :: BuiltinType -> SqlType Other :: Oid -> SqlType data SqlError SqlError :: ByteString -> Int -> ByteString -> SqlError sqlState :: SqlError -> ByteString sqlNativeError :: SqlError -> Int sqlErrorMsg :: SqlError -> ByteString data ConnectInfo ConnectInfo :: String -> Word16 -> String -> String -> String -> ConnectInfo connectHost :: ConnectInfo -> String connectPort :: ConnectInfo -> Word16 connectUser :: ConnectInfo -> String connectPassword :: ConnectInfo -> String connectDatabase :: ConnectInfo -> String -- | Default information for setting up a connection. -- -- Defaults are as follows: -- -- -- -- Use as in the following example: -- --
--   connect defaultConnectInfo { connectHost = "db.example.com" }
--   
defaultConnectInfo :: ConnectInfo -- | Connect with the given username to the given database. Will throw an -- exception if it cannot connect. connect :: ConnectInfo -> IO Connection -- | Attempt to make a connection based on a libpq connection string. See -- http://www.postgresql.org/docs/9.1/static/libpq-connect.html -- for more information. connectPostgreSQL :: ByteString -> IO Connection -- | Turns a ConnectInfo data structure into a libpq connection -- string. postgreSQLConnectionString :: ConnectInfo -> ByteString oid2int :: Oid -> Int exec :: Connection -> ByteString -> IO Result disconnectedError :: SqlError -- | Atomically perform an action with the database handle, if there is -- one. withConnection :: Connection -> (Connection -> IO a) -> IO a close :: Connection -> IO () newNullConnection :: IO Connection data Row Row :: {-# UNPACK #-} !Row -> !Vector ByteString -> !Result -> Row row :: Row -> {-# UNPACK #-} !Row typenames :: Row -> !Vector ByteString rowresult :: Row -> !Result newtype RowParser a RP :: ReaderT Row (StateT Column Ok) a -> RowParser a unRP :: RowParser a -> ReaderT Row (StateT Column Ok) a getvalue :: Result -> Row -> Column -> Maybe ByteString nfields :: Result -> Column instance Typeable SqlError instance Typeable ConnectInfo instance Show SqlError instance Eq ConnectInfo instance Read ConnectInfo instance Show ConnectInfo instance Functor RowParser instance Applicative RowParser instance Alternative RowParser instance Monad RowParser instance Exception SqlError -- | The Result typeclass, for converting a single value in a row -- returned by a SQL query into a more useful Haskell representation. -- -- A Haskell numeric type is considered to be compatible with all -- PostgreSQL numeric types that are less accurate than it. For instance, -- the Haskell Double type is compatible with the PostgreSQL's -- 32-bit Int type because it can represent a Int -- exactly. On the other hand, since a Double might lose precision -- if representing a 64-bit BigInt, the two are not -- considered compatible. module Database.PostgreSQL.Simple.FromField -- | A type that may be converted from a SQL type. class FromField a fromField :: FromField a => Field -> Maybe ByteString -> Ok a -- | Exception thrown if conversion from a SQL value to a Haskell value -- fails. data ResultError -- | The SQL and Haskell types are not compatible. Incompatible :: String -> String -> String -> ResultError errSQLType :: ResultError -> String errHaskellType :: ResultError -> String errMessage :: ResultError -> String -- | A SQL NULL was encountered when the Haskell type did not -- permit it. UnexpectedNull :: String -> String -> String -> ResultError errSQLType :: ResultError -> String errHaskellType :: ResultError -> String errMessage :: ResultError -> String -- | The SQL value could not be parsed, or could not be represented as a -- valid Haskell value, or an unexpected low-level error occurred (e.g. -- mismatch between metadata and actual data in a row). ConversionFailed :: String -> String -> String -> ResultError errSQLType :: ResultError -> String errHaskellType :: ResultError -> String errMessage :: ResultError -> String -- | Given one of the constructors from ResultError, the field, and -- an errMessage, this fills in the other fields in the exception -- value and returns it in a 'Left . SomeException' constructor. returnError :: (Typeable a, Exception err) => (String -> String -> String -> err) -> Field -> String -> Ok a -- | A Field represents metadata about a particular field -- -- You don't particularly want to retain these structures for a long -- period of time, as they will retain the entire query result, not just -- the field metadata data Field typename :: Field -> ByteString name :: Field -> Maybe ByteString tableOid :: Field -> Oid tableColumn :: Field -> Int format :: Field -> Format typeOid :: Field -> Oid newtype Oid :: * Oid :: CUInt -> Oid data Format :: * Text :: Format Binary :: Format instance Typeable ResultError instance Eq ResultError instance Show ResultError instance (FromField a, FromField b) => FromField (Either a b) instance FromField TimeOfDay instance FromField Day instance FromField UTCTime instance FromField [Char] instance FromField Text instance FromField Text instance FromField (Binary ByteString) instance FromField (Binary ByteString) instance FromField ByteString instance FromField Oid instance FromField ByteString instance FromField (Ratio Integer) instance FromField Double instance FromField Float instance FromField Integer instance FromField Int64 instance FromField Int instance FromField Int32 instance FromField Int16 instance FromField Bool instance FromField Null instance FromField a => FromField (Maybe a) instance Exception ResultError -- | The FromRow typeclass, for converting a row of results returned -- by a SQL query into a more useful Haskell representation. -- -- Predefined instances are provided for tuples containing up to ten -- elements. module Database.PostgreSQL.Simple.FromRow -- | 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 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 previous versions of postgresql-simple no longer apply. -- Instead, look at the caveats associated with user-defined -- implementations of fromRow. class FromRow a fromRow :: FromRow a => RowParser a data RowParser a field :: FromField a => RowParser a numFieldsRemaining :: RowParser Int instance (FromRow a, FromRow b) => FromRow (a :. b) instance FromField a => FromRow [a] instance (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 (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 (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 (FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g) => FromRow (a, b, c, d, e, f, g) instance (FromField a, FromField b, FromField c, FromField d, FromField e, FromField f) => FromRow (a, b, c, d, e, f) instance (FromField a, FromField b, FromField c, FromField d, FromField e) => FromRow (a, b, c, d, e) instance (FromField a, FromField b, FromField c, FromField d) => FromRow (a, b, c, d) instance (FromField a, FromField b, FromField c) => FromRow (a, b, c) instance (FromField a, FromField b) => FromRow (a, b) instance FromField a => FromRow (Only a) module Database.PostgreSQL.Simple.LargeObjects loCreat :: Connection -> IO Oid loCreate :: Connection -> Oid -> IO Oid loImport :: Connection -> FilePath -> IO Oid loImportWithOid :: Connection -> FilePath -> Oid -> IO Oid loExport :: Connection -> Oid -> FilePath -> IO () loOpen :: Connection -> Oid -> IOMode -> IO LoFd loWrite :: Connection -> LoFd -> ByteString -> IO Int loRead :: Connection -> LoFd -> Int -> IO ByteString loSeek :: Connection -> LoFd -> SeekMode -> Int -> IO Int loTell :: Connection -> LoFd -> IO Int loTruncate :: Connection -> LoFd -> Int -> IO () loClose :: Connection -> LoFd -> IO () loUnlink :: Connection -> Oid -> IO () newtype Oid :: * Oid :: CUInt -> Oid -- | LoFd is a Large Object (pseudo) File Descriptor. It is understood by -- libpq but not by operating system calls. data LoFd :: * -- | See openFile data IOMode :: * ReadMode :: IOMode WriteMode :: IOMode AppendMode :: IOMode ReadWriteMode :: IOMode -- | A mode that determines the effect of hSeek hdl mode -- i. data SeekMode :: * -- | the position of hdl is set to i. AbsoluteSeek :: SeekMode -- | the position of hdl is set to offset i from the -- current position. RelativeSeek :: SeekMode -- | the position of hdl is set to offset i from the end -- of the file. SeekFromEnd :: SeekMode module Database.PostgreSQL.Simple.Notification data Notification Notification :: CPid -> ByteString -> ByteString -> Notification notificationPid :: Notification -> CPid notificationChannel :: Notification -> ByteString notificationData :: Notification -> ByteString getNotification :: Connection -> IO Notification -- | A mid-level client library for the PostgreSQL database, aimed at ease -- of use and high performance. module Database.PostgreSQL.Simple data ConnectInfo ConnectInfo :: String -> Word16 -> String -> String -> String -> ConnectInfo connectHost :: ConnectInfo -> String connectPort :: ConnectInfo -> Word16 connectUser :: ConnectInfo -> String connectPassword :: ConnectInfo -> String connectDatabase :: ConnectInfo -> String data Connection -- | 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. data Query -- | 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 ?" (In [3,4,5])
--   
newtype In a In :: a -> In a -- | Wrap a mostly-binary string to be escaped in hexadecimal. newtype Binary a Binary :: a -> Binary 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 Only a Only :: a -> Only a fromOnly :: Only a -> a data SqlError SqlError :: ByteString -> Int -> ByteString -> SqlError sqlState :: SqlError -> ByteString sqlNativeError :: SqlError -> Int sqlErrorMsg :: SqlError -> ByteString -- | Exception thrown if a Query could not be formatted correctly. -- This may occur if the number of '?' characters in the query -- string does not match the number of parameters provided. data FormatError -- | Exception thrown if query is used to perform an -- INSERT-like operation, or execute is used to perform a -- SELECT-like operation. data QueryError -- | Exception thrown if conversion from a SQL value to a Haskell value -- fails. data ResultError -- | Connect with the given username to the given database. Will throw an -- exception if it cannot connect. connect :: ConnectInfo -> IO Connection -- | Attempt to make a connection based on a libpq connection string. See -- http://www.postgresql.org/docs/9.1/static/libpq-connect.html -- for more information. connectPostgreSQL :: ByteString -> IO Connection -- | Turns a ConnectInfo data structure into a libpq connection -- string. postgreSQLConnectionString :: ConnectInfo -> ByteString -- | Default information for setting up a connection. -- -- Defaults are as follows: -- -- -- -- Use as in the following example: -- --
--   connect defaultConnectInfo { connectHost = "db.example.com" }
--   
defaultConnectInfo :: ConnectInfo close :: Connection -> IO () -- | Perform a SELECT or other SQL query that is expected to -- return results. All results are retrieved and converted before this -- function returns. -- -- When processing large results, this function will consume a lot of -- client-side memory. Consider using fold instead. -- -- Exceptions that may be thrown: -- -- query :: (ToRow q, FromRow r) => Connection -> Query -> q -> IO [r] -- | A version of query that does not perform query substitution. query_ :: FromRow r => Connection -> Query -> IO [r] data FoldOptions FoldOptions :: !FetchQuantity -> !TransactionMode -> FoldOptions fetchQuantity :: FoldOptions -> !FetchQuantity transactionMode :: FoldOptions -> !TransactionMode data FetchQuantity Automatic :: FetchQuantity Fixed :: !Int -> FetchQuantity defaultFoldOptions :: FoldOptions -- | Perform a SELECT or other SQL query that is expected to -- return results. Results are streamed incrementally from the server, -- and consumed via a left fold. -- -- When dealing with small results, it may be simpler (and perhaps -- faster) to use query instead. -- -- This fold is not strict. The stream consumer is responsible for -- forcing the evaluation of its result to avoid space leaks. -- -- Exceptions that may be thrown: -- -- fold :: (FromRow row, ToRow params) => Connection -> Query -> params -> a -> (a -> row -> IO a) -> IO a foldWithOptions :: (FromRow row, ToRow params) => FoldOptions -> Connection -> Query -> params -> a -> (a -> row -> IO a) -> IO a -- | A version of fold that does not perform query substitution. fold_ :: FromRow r => Connection -> Query -> a -> (a -> r -> IO a) -> IO a foldWithOptions_ :: FromRow r => FoldOptions -> Connection -> Query -> a -> (a -> r -> IO a) -> IO a -- | A version of fold that does not transform a state value. forEach :: (ToRow q, FromRow r) => Connection -> Query -> q -> (r -> IO ()) -> IO () -- | A version of forEach that does not perform query substitution. forEach_ :: FromRow r => Connection -> Query -> (r -> IO ()) -> IO () -- | Execute an INSERT, UPDATE, or other SQL query that -- is not expected to return results. -- -- Returns the number of rows affected. -- -- Throws FormatError if the query could not be formatted -- correctly. execute :: ToRow q => Connection -> Query -> q -> IO Int64 -- | A version of execute that does not perform query substitution. execute_ :: Connection -> Query -> IO Int64 -- | Execute a multi-row INSERT, UPDATE, or other SQL -- query that is not expected to return results. -- -- Returns the number of rows affected. -- -- Throws FormatError if the query could not be formatted -- correctly. executeMany :: ToRow q => Connection -> Query -> [q] -> IO Int64 -- | Execute an action inside a SQL transaction. -- -- This function initiates a transaction with a "begin -- transaction" statement, then executes the supplied action. If the -- action succeeds, the transaction will be completed with commit -- before this function returns. -- -- If the action throws any kind of exception (not just a -- PostgreSQL-related exception), the transaction will be rolled back -- using rollback, then the exception will be rethrown. withTransaction :: Connection -> IO a -> IO a data TransactionMode TransactionMode :: !IsolationLevel -> !ReadWriteMode -> TransactionMode isolationLevel :: TransactionMode -> !IsolationLevel readWriteMode :: TransactionMode -> !ReadWriteMode -- | Of the four isolation levels defined by the SQL standard, these are -- the three levels distinguished by PostgreSQL as of version 9.0. See -- http://www.postgresql.org/docs/9.1/static/transaction-iso.html -- for more information. Note that prior to PostgreSQL 9.0, -- RepeatableRead was equivalent to Serializable. data IsolationLevel -- | the isolation level will be taken from PostgreSQL's per-connection -- default_transaction_isolation variable, which is initialized -- according to the server's config. The default configuration is -- ReadCommitted. DefaultIsolationLevel :: IsolationLevel ReadCommitted :: IsolationLevel RepeatableRead :: IsolationLevel Serializable :: IsolationLevel data ReadWriteMode -- | the read-write mode will be taken from PostgreSQL's per-connection -- default_transaction_read_only variable, which is initialized -- according to the server's config. The default configuration is -- ReadWrite. DefaultReadWriteMode :: ReadWriteMode ReadWrite :: ReadWriteMode ReadOnly :: ReadWriteMode defaultTransactionMode :: TransactionMode defaultIsolationLevel :: IsolationLevel defaultReadWriteMode :: ReadWriteMode -- | Execute an action inside a SQL transaction with a given isolation -- level. withTransactionLevel :: IsolationLevel -> Connection -> IO a -> IO a -- | Execute an action inside a SQL transaction with a given transaction -- mode. withTransactionMode :: TransactionMode -> Connection -> IO a -> IO a -- | Begin a transaction. begin :: Connection -> IO () -- | Begin a transaction with a given isolation level beginLevel :: IsolationLevel -> Connection -> IO () -- | Begin a transaction with a given transaction mode beginMode :: TransactionMode -> Connection -> IO () -- | Commit a transaction. commit :: Connection -> IO () -- | Rollback a transaction. rollback :: Connection -> IO () -- | Format a query string with a variable number of rows. -- -- This function is exposed to help with debugging and logging. Do not -- use it to prepare queries for execution. -- -- The query string must contain exactly one substitution group, -- identified by the SQL keyword "VALUES" (case insensitive) -- followed by an "(" character, a series of one or more -- "?" characters separated by commas, and a ")" -- character. White space in a substitution group is permitted. -- -- Throws FormatError if the query string could not be formatted -- correctly. formatMany :: ToRow q => Connection -> Query -> [q] -> IO ByteString -- | Format a query string. -- -- This function is exposed to help with debugging and logging. Do not -- use it to prepare queries for execution. -- -- String parameters are escaped according to the character set in use on -- the Connection. -- -- Throws FormatError if the query string could not be formatted -- correctly. formatQuery :: ToRow q => Connection -> Query -> q -> IO ByteString instance Typeable FormatError instance Typeable QueryError instance Eq FormatError instance Show FormatError instance Eq QueryError instance Show QueryError instance Show IsolationLevel instance Eq IsolationLevel instance Ord IsolationLevel instance Enum IsolationLevel instance Bounded IsolationLevel instance Show ReadWriteMode instance Eq ReadWriteMode instance Ord ReadWriteMode instance Enum ReadWriteMode instance Bounded ReadWriteMode instance Show TransactionMode instance Eq TransactionMode instance Exception QueryError instance Exception FormatError