opaleye-0.7.3.0: An SQL-generating DSL targeting PostgreSQL
Safe HaskellNone
LanguageHaskell2010

Opaleye.RunSelect

Synopsis

Running Selects

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]

runSelectI Source #

Arguments

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

Version of runSelect with better type inference

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.

Cursor interface

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.

Creating new FromFields

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 DefaultFromField Foo Foo where
   defaultFromField = unsafeFromField Foo defaultFromField

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

Explicit versions

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.

data FromFields columns haskells Source #

A FromFields specifies how to convert Postgres values (fields) 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 FromFields instance.

"FromFields fields haskells" corresponds to postgresql-simple's "RowParser haskells". "Default FromFields columns haskells" corresponds to postgresql-simple's "FromRow haskells".

Instances

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

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

(.#) :: forall a b c q. 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') #

DefaultFromField a b => Default FromFields (Column a) b Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

Methods

def :: FromFields (Column a) b #

Default FromFields fields haskells => Default FromFields (MaybeFields fields) (Maybe haskells) Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Methods

def :: FromFields (MaybeFields fields) (Maybe haskells) #

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 #

Default (Inferrable FromField) a b => Default (Inferrable FromFields) (Column a) b Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable FromFields (Column a) b #

(Default (Inferrable FromField) a b, Maybe b ~ maybe_b) => Default (Inferrable FromFields) (Column (Nullable a)) maybe_b Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable FromFields (Column (Nullable a)) maybe_b #

(Default (Inferrable FromFields) fields haskells, Maybe haskells ~ maybe_haskells) => Default (Inferrable FromFields) (MaybeFields fields) maybe_haskells Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Methods

def :: Inferrable FromFields (MaybeFields fields) maybe_haskells #

data FromField pgType haskellType Source #

A FromField sqlType haskellType encodes how to turn a value of Postgres type sqlType into a value of Haskell type haskellType. For example a value of type FromField SqlText String encodes how to turn a SqlText result from the database into a Haskell String.

"FromField sqlType haskellType" corresponds to postgresql-simple's "FieldParser haskellType".

Instances

Instances details
DefaultFromField 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 #

bytestring ~ ByteString => Default (Inferrable FromField) SqlBytea bytestring Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable FromField SqlBytea bytestring #

cttext ~ CI Text => Default (Inferrable FromField) SqlCitext cttext Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

uuid ~ UUID => Default (Inferrable FromField) SqlUuid uuid Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

localtime ~ LocalTime => Default (Inferrable FromField) SqlTimestamp localtime Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable FromField SqlTimestamp localtime #

timeofday ~ TimeOfDay => Default (Inferrable FromField) SqlTime timeofday Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable FromField SqlTime timeofday #

text ~ Text => Default (Inferrable FromField) SqlText text Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

scientific ~ Scientific => Default (Inferrable FromField) SqlNumeric scientific Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable FromField SqlNumeric scientific #

int ~ Int => Default (Inferrable FromField) SqlInt4 int Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

int64 ~ Int64 => Default (Inferrable FromField) SqlInt8 int64 Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable FromField SqlInt8 int64 #

double ~ Double => Default (Inferrable FromField) SqlFloat8 double Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

day ~ Day => Default (Inferrable FromField) SqlDate day Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

bool ~ Bool => Default (Inferrable FromField) SqlBool bool Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

(Typeable h, Default (Inferrable FromField) f h, hs ~ [h]) => Default (Inferrable FromField) (SqlArray f) hs Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable FromField (SqlArray f) hs #

class DefaultFromField sqlType haskellType where Source #

A DefaultFromField sqlType haskellType represents the default way to turn a sqlType result from the database into a Haskell value of type haskellType.

"DefaultFromField sqlType haskellType" corresponds to postgresql-simple's "FromField haskellType".

Creating an instance of DefaultFromField 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 DefaultFromField instance.

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

Minimal complete definition

queryRunnerColumnDefault | defaultFromField

Methods

defaultFromField :: FromField sqlType haskellType Source #

Instances

Instances details
DefaultFromField SqlJsonb ByteString Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlJsonb ByteString Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlJsonb String Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlJsonb Text Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlJsonb Value Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlJsonb Text Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlJson ByteString Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlJson ByteString Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlJson String Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlJson Text Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlJson Value Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlJson Text Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlBytea ByteString Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlBytea ByteString Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlUuid UUID Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlTimestamptz UTCTime Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlTimestamptz ZonedTime Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlTimestamp LocalTime Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlTime TimeOfDay Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlText String Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlText Text Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlText Text Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlNumeric Scientific Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlInt4 Int Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlInt4 Int32 Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlInt8 Int64 Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlFloat8 Double Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlDate Day Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlBool Bool Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlCitext (CI Text) Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

DefaultFromField SqlCitext (CI Text) Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

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

Defined in Opaleye.Internal.RunQuery

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

Defined in Opaleye.Internal.RunQuery

(Typeable b, DefaultFromField a b) => DefaultFromField (SqlArray a) [b] Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

Helper functions

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

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