Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype CursorName sql = CursorName {
- unCursorName :: sql
- data Scroll
- data Hold
- data Cursor sql
- data CursorDirection
- cursorName :: Cursor sql -> CursorName sql
- cursorQuery :: Cursor sql -> sql
- withCursor :: (IsString sql, IsSQL sql, Monoid sql, MonadDB m, MonadMask m) => CursorName sql -> Scroll -> Hold -> sql -> (Cursor sql -> m r) -> m r
- withCursorSQL :: (MonadDB m, MonadMask m) => CursorName SQL -> Scroll -> Hold -> SQL -> (Cursor SQL -> m r) -> m r
- cursorFetch :: (IsSQL sql, IsString sql, Monoid sql, MonadDB m) => Cursor sql -> CursorDirection -> m Int
- cursorFetch_ :: (IsSQL sql, IsString sql, Monoid sql, MonadDB m) => Cursor sql -> CursorDirection -> m ()
- cursorMove :: (IsSQL sql, IsString sql, Monoid sql, MonadDB m) => Cursor sql -> CursorDirection -> m Int
- cursorMove_ :: (IsSQL sql, IsString sql, Monoid sql, MonadDB m) => Cursor sql -> CursorDirection -> m ()
Documentation
newtype CursorName sql Source #
Name of a cursor.
CursorName | |
|
Instances
Eq sql => Eq (CursorName sql) Source # | |
Defined in Database.PostgreSQL.PQTypes.Cursor (==) :: CursorName sql -> CursorName sql -> Bool # (/=) :: CursorName sql -> CursorName sql -> Bool # | |
Ord sql => Ord (CursorName sql) Source # | |
Defined in Database.PostgreSQL.PQTypes.Cursor 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 # | |
Defined in Database.PostgreSQL.PQTypes.Cursor showsPrec :: Int -> CursorName sql -> ShowS # show :: CursorName sql -> String # showList :: [CursorName sql] -> ShowS # | |
IsString sql => IsString (CursorName sql) Source # | |
Defined in Database.PostgreSQL.PQTypes.Cursor fromString :: String -> CursorName sql # |
Defines whether a cursor will be declared as SCROLL
or NO
SCROLL
. Scrollable cursors can be scrolled in all directions, otherwise only
forward.
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.
Data representing a created cursor.
Instances
Eq sql => Eq (Cursor sql) Source # | |
Ord sql => Ord (Cursor sql) Source # | |
Defined in Database.PostgreSQL.PQTypes.Cursor | |
Show sql => Show (Cursor sql) Source # | |
data CursorDirection Source #
Direction in which to move the cursor. Note that cursors declared as NO
SCROLL
can only move forward (i.e. only CD_Next
, CD_Forward_All
and
CD_Forward
is allowed).
CD_Next | |
CD_Prior | |
CD_First | |
CD_Last | |
CD_Forward_All | |
CD_Backward_All | |
CD_Absolute Int | |
CD_Relative Int | |
CD_Forward Int | |
CD_Backward Int |
Instances
Eq CursorDirection Source # | |
Defined in Database.PostgreSQL.PQTypes.Cursor (==) :: CursorDirection -> CursorDirection -> Bool # (/=) :: CursorDirection -> CursorDirection -> Bool # | |
Ord CursorDirection Source # | |
Defined in Database.PostgreSQL.PQTypes.Cursor compare :: CursorDirection -> CursorDirection -> Ordering # (<) :: CursorDirection -> CursorDirection -> Bool # (<=) :: CursorDirection -> CursorDirection -> Bool # (>) :: CursorDirection -> CursorDirection -> Bool # (>=) :: CursorDirection -> CursorDirection -> Bool # max :: CursorDirection -> CursorDirection -> CursorDirection # min :: CursorDirection -> CursorDirection -> CursorDirection # | |
Show CursorDirection Source # | |
Defined in Database.PostgreSQL.PQTypes.Cursor showsPrec :: Int -> CursorDirection -> ShowS # show :: CursorDirection -> String # showList :: [CursorDirection] -> 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.