opaleye-0.6.7005.0: An SQL-generating DSL targeting PostgreSQL

Safe HaskellNone
LanguageHaskell2010

Opaleye.RunSelect

Contents

Synopsis

Documentation

runSelect Source #

Arguments

:: Default FromFields fields haskells 
=> Connection 
-> Select fields 
-> IO [haskells] 

runSelect's use of the Default FromFields typeclass means that the compiler will have trouble inferring types. It is strongly recommended that you provide full type signatures when using runSelect.

Example type specialization:

runSelect :: Select (Field SqlInt4, Field SqlText) -> IO [(Int, String)]

Assuming the makeAdaptorAndInstance splice has been run for the product type Foo:

runSelect :: Select (Foo (Field SqlInt4) (Field SqlText) (Field SqlBool)
          -> IO [Foo Int String Bool]

runSelectTF Source #

Arguments

:: Default FromFields (rec O) (rec H) 
=> Connection 
-> Select (rec O) 
-> IO [rec H] 

runSelectTF has better type inference than runSelect but only works with "higher-kinded data" types.

runSelectFold Source #

Arguments

:: Default FromFields fields haskells 
=> Connection 
-> Select fields 
-> b 
-> (b -> haskells -> IO b) 
-> IO b 

runSelectFold streams the results of a query incrementally and consumes the results with a left fold.

This fold is not strict. The stream consumer is responsible for forcing the evaluation of its result to avoid space leaks.

declareCursor Source #

Arguments

:: Default FromFields fields haskells 
=> Connection 
-> Select fields 
-> IO (Cursor haskells) 

Declare a temporary cursor. The cursor is given a unique name for the given connection.

closeCursor :: Cursor fields -> IO () Source #

Close the given cursor.

foldForward Source #

Arguments

:: Cursor haskells 
-> Int 
-> (a -> haskells -> IO a) 
-> a 
-> IO (Either a a) 

Fold over a chunk of rows, calling the supplied fold-like function on each row as it is received. In case the cursor is exhausted, a Left value is returned, otherwise a Right value is returned.

unsafeFromField :: (b -> b') -> FromField sqlType b -> FromField sqlType' b' Source #

Use unsafeFromField to make an instance to allow you to run queries on your own datatypes. For example:

newtype Foo = Foo Int

instance QueryRunnerColumnDefault Foo Foo where
   defaultFromField = unsafeFromField Foo defaultFromField

It is "unsafe" because it does not check that the sqlType correctly corresponds to the Haskell type.

runSelectExplicit :: FromFields fields haskells -> Connection -> Select fields -> IO [haskells] Source #

runSelectFoldExplicit :: FromFields fields haskells -> Connection -> Select fields -> b -> (b -> haskells -> IO b) -> IO b Source #

declareCursorExplicit :: FromFields fields haskells -> Connection -> Select fields -> IO (Cursor haskells) Source #

Datatypes

data Cursor haskells Source #

Cursor within a transaction.

defaultFromField :: QueryRunnerColumnDefault sqlType haskellType => FromField sqlType haskellType Source #

Helper functions

fromPGSFromField :: FromField haskell => FromField pgType haskell Source #

fromPGSFieldParser :: FieldParser haskell -> FromField pgType haskell Source #