| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Opaleye.RunQuery
Description
This module will be deprecated in 0.7. Use Opaleye.RunSelect instead.
Synopsis
- runQuery :: Default FromFields fields haskells => Connection -> Select fields -> IO [haskells]
- runQueryFold :: Default FromFields fields haskells => Connection -> Select fields -> b -> (b -> haskells -> IO b) -> IO b
- queryRunnerColumn :: (Column a' -> Column a) -> (b -> b') -> QueryRunnerColumn a b -> QueryRunnerColumn a' b'
- runQueryExplicit :: FromFields fields haskells -> Connection -> Select fields -> IO [haskells]
- runQueryFoldExplicit :: FromFields fields haskells -> Connection -> Select fields -> b -> (b -> haskells -> IO b) -> IO b
- declareCursor :: Default FromFields fields haskells => Connection -> Select fields -> IO (Cursor haskells)
- declareCursorExplicit :: FromFields fields haskells -> Connection -> Select fields -> IO (Cursor haskells)
- closeCursor :: Cursor fields -> IO ()
- foldForward :: Cursor haskells -> Int -> (a -> haskells -> IO a) -> a -> IO (Either a a)
- prepareQuery :: FromFields fields haskells -> Select fields -> (Maybe Query, RowParser haskells)
- data Cursor haskells
- type FromFields = QueryRunner
- type FromField = QueryRunnerColumn
- data QueryRunner columns haskells
- data QueryRunnerColumn pgType haskellType
- class QueryRunnerColumnDefault pgType haskellType where
- fieldQueryRunnerColumn :: FromField haskell => FromField pgType haskell
- fieldParserQueryRunnerColumn :: FieldParser haskell -> FromField pgType haskell
Documentation
runQuery :: Default FromFields fields haskells => Connection -> Select fields -> 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 ::Select(ColumnSqlInt4, ColumnSqlText) -> IO [(Int, String)]
Assuming the makeAdaptorAndInstance splice has been run for the product type Foo:
runQuery ::Select(Foo (ColumnSqlInt4) (ColumnSqlText) (ColumnSqlBool) -> IO [Foo Int String Bool]
Opaleye types are converted to Haskell types based on instances of
 the QueryRunnerColumnDefault typeclass.
runQueryFold :: Default FromFields fields haskells => Connection -> Select fields -> 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.
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 SqlInt4)
                         Foo
                         queryRunnerColumnDefault
runQueryExplicit :: FromFields fields haskells -> Connection -> Select fields -> IO [haskells] Source #
runQueryFoldExplicit :: FromFields fields haskells -> Connection -> Select fields -> b -> (b -> haskells -> IO b) -> IO b Source #
declareCursor :: Default FromFields fields haskells => Connection -> Select fields -> IO (Cursor haskells) Source #
Declare a temporary cursor. The cursor is given a unique name for the given connection.
Returns Nothing when the query returns zero rows.
declareCursorExplicit :: FromFields fields haskells -> Connection -> Select fields -> IO (Cursor haskells) Source #
Like declareCursor but takes a FromFields explicitly.
closeCursor :: Cursor fields -> IO () Source #
Close the given cursor.
prepareQuery :: FromFields fields haskells -> Select fields -> (Maybe Query, RowParser haskells) Source #
Deprecated: Will be removed in version 0.7
Datatypes
type FromFields = QueryRunner Source #
type FromField = QueryRunnerColumn Source #
data QueryRunner columns haskells Source #
A QueryRunner specifies how to convert Postgres values (columns)
   into Haskell values (haskells).  Most likely you will never need
   to create on of these or handle one directly.  It will be provided
   for you by the Default QueryRunner instance.
"QueryRunner columns haskells" corresponds to
 postgresql-simple's "RowParser haskells".  "Default
 QueryRunner columns haskells" corresponds to
 postgresql-simple's "FromRow haskells".
Instances
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.
"QueryRunnerColumn pgType haskellType" corresponds to
 postgresql-simple's "FieldParser haskellType".
Instances
| QueryRunnerColumnDefault sqlType haskellType => Default FromField sqlType haskellType Source # | |
| Defined in Opaleye.Internal.RunQuery | |
| Functor (FromField u) Source # | |
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 haskellType.
"QueryRunnerColumnDefault pgType haskellType" corresponds
 to postgresql-simple's "FromField haskellType".
Creating an instance of QueryRunnerColumnDefault for your own types is
 necessary for retrieving those types from the database.
You should use one of the three methods below for writing a
 QueryRunnerColumnDefault instance.
- If you already have a FromFieldinstance for yourhaskellType, usefieldQueryRunnerColumn. (This is how most of the built-in instances are defined.)
- If you don't have a FromFieldinstance, usequeryRunnerColumnif possible. See the documentation forqueryRunnerColumnfor an example.
- If you have a more complicated case, but not a FromFieldinstance, write aFieldParserfor your type and usefieldParserQueryRunnerColumn. You can also add aFromFieldinstance using this.
Minimal complete definition
Methods
queryRunnerColumnDefault :: QueryRunnerColumn pgType haskellType Source #
Instances
Creating new QueryRunnerColumns
fieldQueryRunnerColumn :: FromField haskell => FromField pgType haskell Source #
fieldParserQueryRunnerColumn :: FieldParser haskell -> FromField pgType haskell Source #