opaleye-0.5.3.0: An SQL-generating DSL targeting PostgreSQL

Safe HaskellNone
LanguageHaskell2010

Opaleye.RunQuery

Contents

Synopsis

Running Querys

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 [(Int, String)]

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

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

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

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.

Creating new QueryRunnerColumns

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

Explicit versions

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

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

Deprecated functions

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

For internal use only. Do not use. Will be deprecated in version 0.6.

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.

Instances

SumProfunctor QueryRunner Source # 

Methods

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

ProductProfunctor QueryRunner Source # 

Methods

empty :: QueryRunner () () #

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

Profunctor QueryRunner Source # 

Methods

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

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

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

(#.) :: Coercible * c b => (b -> c) -> QueryRunner a b -> QueryRunner a c #

(.#) :: Coercible * b a => QueryRunner b c -> (a -> b) -> QueryRunner a c #

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

Methods

def :: QueryRunner (Column a) b #

Functor (QueryRunner c) Source # 

Methods

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

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

Applicative (QueryRunner c) Source # 

Methods

pure :: a -> QueryRunner c a #

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

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

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

Datatypes

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.

Instances

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.

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 # 
QueryRunnerColumnDefault PGJsonb Value Source # 
QueryRunnerColumnDefault PGJson String Source # 
QueryRunnerColumnDefault PGJson Value Source # 
QueryRunnerColumnDefault PGBytea ByteString Source # 
QueryRunnerColumnDefault PGBytea ByteString Source # 
QueryRunnerColumnDefault PGUuid UUID Source # 
QueryRunnerColumnDefault PGTimestamptz UTCTime Source # 
QueryRunnerColumnDefault PGTimestamp LocalTime Source # 
QueryRunnerColumnDefault PGTime TimeOfDay Source # 
QueryRunnerColumnDefault PGText String Source # 
QueryRunnerColumnDefault PGText Text Source # 
QueryRunnerColumnDefault PGText Text Source # 
QueryRunnerColumnDefault PGInt4 Int Source # 
QueryRunnerColumnDefault PGInt4 Int32 Source # 
QueryRunnerColumnDefault PGInt8 Int64 Source # 
QueryRunnerColumnDefault PGFloat8 Double Source # 
QueryRunnerColumnDefault PGDate Day Source # 
QueryRunnerColumnDefault PGBool Bool Source # 
QueryRunnerColumnDefault PGCitext (CI Text) Source # 
QueryRunnerColumnDefault PGCitext (CI Text) Source # 
QueryRunnerColumnDefault a b => QueryRunnerColumnDefault (Nullable a) (Maybe b) Source # 
(Typeable * b, FromField b, QueryRunnerColumnDefault a b) => QueryRunnerColumnDefault (PGRange a) (PGRange b) Source # 
(Typeable * b, QueryRunnerColumnDefault a b) => QueryRunnerColumnDefault (PGArray a) [b] Source # 

Creating now QueryRunnerColumns