hpqtypes-1.8.0.1: Haskell bindings to libpqtypes

Safe HaskellNone
LanguageHaskell2010

Database.PostgreSQL.PQTypes.Cursor

Synopsis

Documentation

newtype CursorName sql Source #

Name of a cursor.

Constructors

CursorName 

Fields

Instances
Eq sql => Eq (CursorName sql) Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.Cursor

Methods

(==) :: CursorName sql -> CursorName sql -> Bool #

(/=) :: CursorName sql -> CursorName sql -> Bool #

Ord sql => Ord (CursorName sql) Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.Cursor

Methods

compare :: CursorName sql -> CursorName sql -> Ordering #

(<) :: CursorName sql -> CursorName sql -> Bool #

(<=) :: CursorName sql -> CursorName sql -> Bool #

(>) :: CursorName sql -> CursorName sql -> Bool #

(>=) :: CursorName sql -> CursorName sql -> Bool #

max :: CursorName sql -> CursorName sql -> CursorName sql #

min :: CursorName sql -> CursorName sql -> CursorName sql #

Show sql => Show (CursorName sql) Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.Cursor

Methods

showsPrec :: Int -> CursorName sql -> ShowS #

show :: CursorName sql -> String #

showList :: [CursorName sql] -> ShowS #

IsString sql => IsString (CursorName sql) Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.Cursor

Methods

fromString :: String -> CursorName sql #

data Scroll Source #

Defines whether a cursor will be declared as SCROLL or NO SCROLL. Scrollable cursors can be scrolled in all directions, otherwise only forward.

Constructors

Scroll 
NoScroll 
Instances
Eq Scroll Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.Cursor

Methods

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

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

Ord Scroll Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.Cursor

Show Scroll Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.Cursor

data Hold Source #

Defines whether a cursor will be declared as WITH HOLD or WITHOUT HOLD. Cursors declared as WITH HOLD can only be declared within a transaction block and they're automatically closed once the transaction finishes, otherwise they're independent of the current transaction and can be declared even if no transaction is active.

Constructors

Hold 
NoHold 
Instances
Eq Hold Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.Cursor

Methods

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

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

Ord Hold Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.Cursor

Methods

compare :: Hold -> Hold -> Ordering #

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

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

(>) :: Hold -> Hold -> Bool #

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

max :: Hold -> Hold -> Hold #

min :: Hold -> Hold -> Hold #

Show Hold Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.Cursor

Methods

showsPrec :: Int -> Hold -> ShowS #

show :: Hold -> String #

showList :: [Hold] -> ShowS #

data Cursor sql Source #

Data representing a created cursor.

Instances
Eq sql => Eq (Cursor sql) Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.Cursor

Methods

(==) :: Cursor sql -> Cursor sql -> Bool #

(/=) :: Cursor sql -> Cursor sql -> Bool #

Ord sql => Ord (Cursor sql) Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.Cursor

Methods

compare :: Cursor sql -> Cursor sql -> Ordering #

(<) :: Cursor sql -> Cursor sql -> Bool #

(<=) :: Cursor sql -> Cursor sql -> Bool #

(>) :: Cursor sql -> Cursor sql -> Bool #

(>=) :: Cursor sql -> Cursor sql -> Bool #

max :: Cursor sql -> Cursor sql -> Cursor sql #

min :: Cursor sql -> Cursor sql -> Cursor sql #

Show sql => Show (Cursor sql) Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.Cursor

Methods

showsPrec :: Int -> Cursor sql -> ShowS #

show :: Cursor sql -> String #

showList :: [Cursor sql] -> ShowS #

cursorName :: Cursor sql -> CursorName sql Source #

Retrieve the name of a cursor.

cursorQuery :: Cursor sql -> sql Source #

Retrieve SQL query used to create a cursor.

withCursor :: (IsString sql, IsSQL sql, Monoid sql, MonadDB m, MonadMask m) => CursorName sql -> Scroll -> Hold -> sql -> (Cursor sql -> m r) -> m r Source #

Create a cursor from the SQL query and use it within the given context.

withCursorSQL :: (MonadDB m, MonadMask m) => CursorName SQL -> Scroll -> Hold -> SQL -> (Cursor SQL -> m r) -> m r Source #

Version of withCursor without the sql type parameter for convenience.

cursorFetch :: (IsSQL sql, IsString sql, Monoid sql, MonadDB m) => Cursor sql -> CursorDirection -> m Int Source #

Retrieve rows from a query using a cursor. See https://www.postgresql.org/docs/current/sql-fetch.html for more information.

cursorFetch_ :: (IsSQL sql, IsString sql, Monoid sql, MonadDB m) => Cursor sql -> CursorDirection -> m () Source #

Same as cursorFetch, except the result (i.e. the number of fetched rows) is ignored.

cursorMove :: (IsSQL sql, IsString sql, Monoid sql, MonadDB m) => Cursor sql -> CursorDirection -> m Int Source #

Move a cursor to a specific position. It works exactly like cursorFetch, except it only positions the cursor and does not return rows. See https://www.postgresql.org/docs/current/sql-move.html for more information.

cursorMove_ :: (IsSQL sql, IsString sql, Monoid sql, MonadDB m) => Cursor sql -> CursorDirection -> m () Source #

Same as cursorMove, except the result (i.e. the number of rows that would be fetched) is ignored.