opaleye-0.5.0.0: An SQL-generating DSL targeting PostgreSQL

Safe HaskellNone
LanguageHaskell98

Opaleye.RunQuery

Synopsis

Documentation

runQuery :: Default QueryRunner columns haskells => Connection -> Query columns -> IO [haskells] Source

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

Example type specialization:

runQuery :: Query (Column PGInt4, Column PGText) -> IO [(Column Int, Column String)]

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

runQuery :: Query (Foo (Column PGInt4) (Column PGText) (Column PGBool)
         -> IO [(Foo (Column Int) (Column String) (Column Bool)]

Opaleye types are converted to Haskell types based on instances of the QueryRunnerColumnDefault typeclass.

runQueryExplicit :: QueryRunner columns haskells -> Connection -> Query columns -> IO [haskells] Source

runQueryFold :: Default QueryRunner columns haskells => Connection -> Query columns -> b -> (b -> haskells -> IO b) -> IO b Source

runQueryFold 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.

runQueryFoldExplicit :: QueryRunner columns haskells -> Connection -> Query columns -> b -> (b -> haskells -> IO b) -> IO b Source

queryRunnerColumn :: (Column a' -> Column a) -> (b -> b') -> QueryRunnerColumn a b -> QueryRunnerColumn a' b' Source

Use queryRunnerColumn 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
   queryRunnerColumnDefault =
       queryRunnerColumn (unsafeCoerceColumn
                              :: Column Foo -> Column PGInt4)
                         Foo
                         queryRunnerColumnDefault

prepareQuery :: QueryRunner columns haskells -> Query columns -> (Maybe Query, RowParser haskells) Source

For internal use only. Do not use. Will be removed in a subsequent release.

data QueryRunnerColumn pgType haskellType Source

A QueryRunnerColumn pgType haskellType encodes how to turn a value of Postgres type pgType into a value of Haskell type haskellType. For example a value of type QueryRunnerColumn PGText String encodes how to turn a PGText result from the database into a Haskell String.

class QueryRunnerColumnDefault pgType haskellType where Source

A QueryRunnerColumnDefault pgType haskellType represents the default way to turn a pgType result from the database into a Haskell value of type haskelType.