opaleye-0.6.7003.1: An SQL-generating DSL targeting PostgreSQL

Safe HaskellNone
LanguageHaskell2010

Opaleye.RunQuery

Contents

Description

This module will be deprecated in 0.7. Use Opaleye.RunSelect instead.

Synopsis

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 (Column SqlInt4, Column SqlText) -> IO [(Int, String)]

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

runQuery :: Select (Foo (Column SqlInt4) (Column SqlText) (Column SqlBool)
         -> 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.

foldForward :: Cursor haskells -> Int -> (a -> haskells -> IO a) -> a -> IO (Either a a) Source #

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.

prepareQuery :: FromFields fields haskells -> Select fields -> (Maybe Query, RowParser haskells) Source #

Deprecated: Will be removed in version 0.7

Datatypes

data Cursor haskells Source #

Cursor within a transaction.

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
Profunctor FromFields Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

Methods

dimap :: (a -> b) -> (c -> d) -> FromFields b c -> FromFields a d #

lmap :: (a -> b) -> FromFields b c -> FromFields a c #

rmap :: (b -> c) -> FromFields a b -> FromFields a c #

(#.) :: Coercible c b => q b c -> FromFields a b -> FromFields a c #

(.#) :: Coercible b a => FromFields b c -> q a b -> FromFields a c #

ProductProfunctor FromFields Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

Methods

purePP :: b -> FromFields a b #

(****) :: FromFields a (b -> c) -> FromFields a b -> FromFields a c #

empty :: FromFields () () #

(***!) :: FromFields a b -> FromFields a' b' -> FromFields (a, a') (b, b') #

SumProfunctor FromFields Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

Methods

(+++!) :: FromFields a b -> FromFields a' b' -> FromFields (Either a a') (Either b b') #

QueryRunnerColumnDefault a b => Default QueryRunner (Column a) b Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

Methods

def :: QueryRunner (Column a) b #

Functor (FromFields c) Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

Methods

fmap :: (a -> b) -> FromFields c a -> FromFields c b #

(<$) :: a -> FromFields c b -> FromFields c a #

Applicative (FromFields c) Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

Methods

pure :: a -> FromFields c a #

(<*>) :: FromFields c (a -> b) -> FromFields c a -> FromFields c b #

liftA2 :: (a -> b -> c0) -> FromFields c a -> FromFields c b -> FromFields c c0 #

(*>) :: FromFields c a -> FromFields c b -> FromFields c b #

(<*) :: FromFields c a -> FromFields c b -> FromFields c a #

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 # 
Instance details

Defined in Opaleye.Internal.RunQuery

Methods

def :: FromField sqlType haskellType #

Functor (FromField u) Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

Methods

fmap :: (a -> b) -> FromField u a -> FromField u b #

(<$) :: a -> FromField u b -> FromField u a #

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.

  1. If you already have a FromField instance for your haskellType, use fieldQueryRunnerColumn. (This is how most of the built-in instances are defined.)
  2. If you don't have a FromField instance, use queryRunnerColumn if possible. See the documentation for queryRunnerColumn for an example.
  3. If you have a more complicated case, but not a FromField instance, write a FieldParser for your type and use fieldParserQueryRunnerColumn. You can also add a FromField instance using this.

Minimal complete definition

queryRunnerColumnDefault

Methods

queryRunnerColumnDefault :: QueryRunnerColumn pgType haskellType Source #

Instances
QueryRunnerColumnDefault PGJsonb String Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

QueryRunnerColumnDefault PGJsonb Value Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

QueryRunnerColumnDefault PGJson String Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

QueryRunnerColumnDefault PGJson Value Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

QueryRunnerColumnDefault PGBytea ByteString Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

QueryRunnerColumnDefault PGBytea ByteString Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

QueryRunnerColumnDefault PGUuid UUID Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

QueryRunnerColumnDefault PGTimestamptz UTCTime Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

QueryRunnerColumnDefault PGTimestamptz ZonedTime Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

QueryRunnerColumnDefault PGTimestamp LocalTime Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

QueryRunnerColumnDefault PGTime TimeOfDay Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

QueryRunnerColumnDefault PGText String Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

QueryRunnerColumnDefault PGText Text Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

QueryRunnerColumnDefault PGText Text Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

QueryRunnerColumnDefault PGNumeric Scientific Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

QueryRunnerColumnDefault PGInt4 Int Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

QueryRunnerColumnDefault PGInt4 Int32 Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

QueryRunnerColumnDefault PGInt8 Int64 Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

QueryRunnerColumnDefault PGFloat8 Double Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

QueryRunnerColumnDefault PGDate Day Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

QueryRunnerColumnDefault PGBool Bool Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

QueryRunnerColumnDefault PGCitext (CI Text) Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

QueryRunnerColumnDefault PGCitext (CI Text) Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

QueryRunnerColumnDefault a b => QueryRunnerColumnDefault (Nullable a) (Maybe b) Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

(Typeable b, FromField b, QueryRunnerColumnDefault a b) => QueryRunnerColumnDefault (PGRange a) (PGRange b) Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

(Typeable b, QueryRunnerColumnDefault a b) => QueryRunnerColumnDefault (PGArray a) [b] Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

Creating new QueryRunnerColumns

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