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

Opaleye

Description

An SQL-generating DSL targeting PostgreSQL. Allows Postgres queries to be written within Haskell in a typesafe and composable fashion.

You might like to look at

Synopsis

Documentation

type Constant = ToFields Source #

Deprecated: Use ToFields instead. Will be removed in version 0.8.

newtype ToFields haskells fields Source #

Constructors

ToFields 

Fields

Instances

Instances details
Profunctor ToFields Source # 
Instance details

Defined in Opaleye.Internal.Constant

Methods

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

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

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

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

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

ProductProfunctor ToFields Source # 
Instance details

Defined in Opaleye.Internal.Constant

Methods

purePP :: b -> ToFields a b #

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

empty :: ToFields () () #

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

SumProfunctor ToFields Source # 
Instance details

Defined in Opaleye.Internal.Constant

Methods

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

Default ToFields Bool (Column SqlBool) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields Double (Column SqlFloat8) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields Int (Column SqlInt4) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields Int32 (Column SqlInt4) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields Int64 (Column SqlInt8) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields ByteString (Column SqlJsonb) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields ByteString (Column SqlJson) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields ByteString (Column SqlBytea) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields ByteString (Column SqlJsonb) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields ByteString (Column SqlJson) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields ByteString (Column SqlBytea) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields Scientific (Column SqlNumeric) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields String (Column SqlText) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields Text (Column SqlText) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields UTCTime (Column SqlTimestamptz) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields Value (Column SqlJsonb) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields Value (Column SqlJson) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields Text (Column SqlText) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields ZonedTime (Column SqlTimestamptz) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields LocalTime (Column SqlTimestamp) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields TimeOfDay (Column SqlTime) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields Day (Column SqlDate) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields UUID (Column SqlUuid) Source # 
Instance details

Defined in Opaleye.Internal.Constant

(Default ToFields a (Column b), IsSqlType b) => Default ToFields [a] (Column (SqlArray b)) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Methods

def :: ToFields [a] (Column (SqlArray b)) #

Default ToFields haskell (Column sql) => Default ToFields (Maybe haskell) (Maybe (Column sql)) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Methods

def :: ToFields (Maybe haskell) (Maybe (Column sql)) #

Default ToFields haskell (Column sql) => Default ToFields (Maybe haskell) (Column (Nullable sql)) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Methods

def :: ToFields (Maybe haskell) (Column (Nullable sql)) #

(Default ToFields a b, Default Nullspec a b) => Default ToFields (Maybe a) (MaybeFields b) Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Methods

def :: ToFields (Maybe a) (MaybeFields b) #

Default ToFields (CI Text) (Column SqlCitext) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields (CI Text) (Column SqlCitext) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields (PGRange Int) (Column (SqlRange SqlInt4)) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields (PGRange Int64) (Column (SqlRange SqlInt8)) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields (PGRange Scientific) (Column (SqlRange SqlNumeric)) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields (PGRange UTCTime) (Column (SqlRange SqlTimestamptz)) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields (PGRange LocalTime) (Column (SqlRange SqlTimestamp)) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields (PGRange Day) (Column (SqlRange SqlDate)) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields (Column a) (Column a) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Methods

def :: ToFields (Column a) (Column a) #

Functor (ToFields a) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Methods

fmap :: (a0 -> b) -> ToFields a a0 -> ToFields a b #

(<$) :: a0 -> ToFields a b -> ToFields a a0 #

Applicative (ToFields a) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Methods

pure :: a0 -> ToFields a a0 #

(<*>) :: ToFields a (a0 -> b) -> ToFields a a0 -> ToFields a b #

liftA2 :: (a0 -> b -> c) -> ToFields a a0 -> ToFields a b -> ToFields a c #

(*>) :: ToFields a a0 -> ToFields a b -> ToFields a b #

(<*) :: ToFields a a0 -> ToFields a b -> ToFields a a0 #

Column SqlBool ~ cSqlBool => Default (Inferrable ToFields) Bool cSqlBool Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable ToFields Bool cSqlBool #

Column SqlFloat8 ~ cSqlFloat8 => Default (Inferrable ToFields) Double cSqlFloat8 Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable ToFields Double cSqlFloat8 #

Column SqlInt4 ~ cSqlInt4 => Default (Inferrable ToFields) Int cSqlInt4 Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable ToFields Int cSqlInt4 #

Column SqlInt4 ~ cSqlInt4 => Default (Inferrable ToFields) Int32 cSqlInt4 Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable ToFields Int32 cSqlInt4 #

Column SqlInt8 ~ cSqlInt8 => Default (Inferrable ToFields) Int64 cSqlInt8 Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable ToFields Int64 cSqlInt8 #

Column SqlBytea ~ cSqlBytea => Default (Inferrable ToFields) ByteString cSqlBytea Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable ToFields ByteString cSqlBytea #

Column SqlBytea ~ cSqlBytea => Default (Inferrable ToFields) ByteString cSqlBytea Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable ToFields ByteString cSqlBytea #

Column SqlNumeric ~ cSqlNumeric => Default (Inferrable ToFields) Scientific cSqlNumeric Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable ToFields Scientific cSqlNumeric #

Column SqlText ~ cSqlText => Default (Inferrable ToFields) String cSqlText Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable ToFields String cSqlText #

Column SqlText ~ cSqlText => Default (Inferrable ToFields) Text cSqlText Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable ToFields Text cSqlText #

Column SqlTimestamptz ~ cSqlTimestamptz => Default (Inferrable ToFields) UTCTime cSqlTimestamptz Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable ToFields UTCTime cSqlTimestamptz #

Column SqlText ~ cSqlText => Default (Inferrable ToFields) Text cSqlText Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable ToFields Text cSqlText #

Column SqlTimestamptz ~ cSqlTimestamptz => Default (Inferrable ToFields) ZonedTime cSqlTimestamptz Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable ToFields ZonedTime cSqlTimestamptz #

Column SqlTime ~ cSqlTime => Default (Inferrable ToFields) TimeOfDay cSqlTime Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable ToFields TimeOfDay cSqlTime #

Column SqlDate ~ cSqlDate => Default (Inferrable ToFields) Day cSqlDate Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable ToFields Day cSqlDate #

Column SqlUuid ~ cSqlUuid => Default (Inferrable ToFields) UUID cSqlUuid Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable ToFields UUID cSqlUuid #

(Default (Inferrable ToFields) a b, Default Nullspec a b, MaybeFields b ~ maybeFields_b) => Default (Inferrable ToFields) (Maybe a) maybeFields_b Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Methods

def :: Inferrable ToFields (Maybe a) maybeFields_b #

Column SqlCitext ~ cSqlCitext => Default (Inferrable ToFields) (CI Text) cSqlCitext Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable ToFields (CI Text) cSqlCitext #

Column SqlCitext ~ cSqlCitext => Default (Inferrable ToFields) (CI Text) cSqlCitext Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable ToFields (CI Text) cSqlCitext #

Column (SqlRange SqlInt4) ~ cRangeInt4 => Default (Inferrable ToFields) (PGRange Int) cRangeInt4 Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable ToFields (PGRange Int) cRangeInt4 #

Column (SqlRange SqlInt8) ~ cRangeInt8 => Default (Inferrable ToFields) (PGRange Int64) cRangeInt8 Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable ToFields (PGRange Int64) cRangeInt8 #

Column (SqlRange SqlNumeric) ~ cRangeScientific => Default (Inferrable ToFields) (PGRange Scientific) cRangeScientific Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable ToFields (PGRange Scientific) cRangeScientific #

Column (SqlRange SqlTimestamptz) ~ cRangeTimestamptz => Default (Inferrable ToFields) (PGRange UTCTime) cRangeTimestamptz Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable ToFields (PGRange UTCTime) cRangeTimestamptz #

Column (SqlRange SqlTimestamp) ~ cRangeTimestamp => Default (Inferrable ToFields) (PGRange LocalTime) cRangeTimestamp Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable ToFields (PGRange LocalTime) cRangeTimestamp #

Column (SqlRange SqlDate) ~ cRangeDate => Default (Inferrable ToFields) (PGRange Day) cRangeDate Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable ToFields (PGRange Day) cRangeDate #

Column a ~ columnA => Default (Inferrable ToFields) (Column a) columnA Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable ToFields (Column a) columnA #

constant :: Default ToFields haskells fields => haskells -> fields Source #

Deprecated: Use toFields instead. Will be removed in version 0.8.

toToFields :: (haskells -> fields) -> ToFields haskells fields Source #

data Nullability Source #

Constructors

NonNullable 
Nullable 

Instances

Instances details
type A ('H NullsT :: Arr Type (TC a) k2) ('TC '(t, b) :: TC a) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A ('H NullsT :: Arr Type (TC a) k2) ('TC '(t, b) :: TC a) = A ('H NullsT :: Arr Type (C a) k2) ('C t)
type A ('H WT :: Arr Type (TC a) k2) ('TC '(t, Req) :: TC a) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A ('H WT :: Arr Type (TC a) k2) ('TC '(t, Req) :: TC a) = A ('H OT :: Arr Type (C a) k2) ('C t)
type A ('H OT :: Arr Type (TC a) k2) ('TC '(t, b) :: TC a) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A ('H OT :: Arr Type (TC a) k2) ('TC '(t, b) :: TC a) = A ('H OT :: Arr Type (C a) k2) ('C t)
type A ('H HT :: Arr Type (TC a) k2) ('TC '(t, b) :: TC a) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A ('H HT :: Arr Type (TC a) k2) ('TC '(t, b) :: TC a) = A ('H HT :: Arr Type (C a) k2) ('C t)
type A ('H HT :: Arr Type (C k2) k2) ('C '(h, o, NN) :: C k2) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A ('H HT :: Arr Type (C k2) k2) ('C '(h, o, NN) :: C k2) = h
type A ('H WT :: Arr Type (TC a) Type) ('TC '(t, Opt) :: TC a) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A ('H WT :: Arr Type (TC a) Type) ('TC '(t, Opt) :: TC a) = Maybe (A ('H OT :: Arr Type (C a) Type) ('C t))
type A ('H NullsT :: Arr Type (C Type) Type) ('C '(h, o, n) :: C Type) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A ('H NullsT :: Arr Type (C Type) Type) ('C '(h, o, n) :: C Type) = Column (Nullable o)
type A ('H OT :: Arr Type (C Type) Type) ('C '(h, o, N) :: C Type) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A ('H OT :: Arr Type (C Type) Type) ('C '(h, o, N) :: C Type) = Column (Nullable o)
type A ('H OT :: Arr Type (C Type) Type) ('C '(h, o, NN) :: C Type) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A ('H OT :: Arr Type (C Type) Type) ('C '(h, o, NN) :: C Type) = Column o
type A ('H HT :: Arr Type (C Type) Type) ('C '(h, o, N) :: C Type) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A ('H HT :: Arr Type (C Type) Type) ('C '(h, o, N) :: C Type) = Maybe h

type family Field_ (a :: Nullability) b Source #

The name Column will be replaced by Field in version 0.8. The Field_, Field and FieldNullable types exist to help smooth the transition. We recommend that you use Field_, Field or FieldNullable instead of Column everywhere that it is sufficient.

Instances

Instances details
type Field_ 'NonNullable a Source # 
Instance details

Defined in Opaleye.Field

type Field_ 'Nullable a Source # 
Instance details

Defined in Opaleye.Field

optionalRestrict Source #

Arguments

:: Default Unpackspec a a 
=> Select a

Input query

-> SelectArr (a -> Field SqlBool) (MaybeFields a)

If any rows of the input query satisfy the condition then return them (wrapped in "Just"). If none of them satisfy the condition then return a single row of "Nothing"

Convenient access to left/right join functionality. Performs a LEFT JOIN under the hood and has behaviour equivalent to the following Haskell function:

optionalRestrict :: [a] -> (a -> Bool) -> [Maybe a]
optionalRestrict xs p =
   case filter p xs of []  -> [Nothing]
                       xs' -> map Just xs'

For example,

> let l = [1, 10, 100, 1000] :: [Field SqlInt4]
> runSelect conn (proc () -> optionalRestrict (valuesSafe l) -< (.> 100000)) :: IO [Maybe Int]
[Nothing]

> runSelect conn (proc () -> optionalRestrict (valuesSafe l) -< (.> 15)) :: IO [Maybe Int]
[Just 100,Just 1000]

See the documentation of leftJoin for how to use optionalRestrict to replace leftJoin (and by symmetry, rightJoin).

leftJoin Source #

Arguments

:: (Default Unpackspec fieldsL fieldsL, Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsR nullableFieldsR) 
=> Select fieldsL

Left query

-> Select fieldsR

Right query

-> ((fieldsL, fieldsR) -> Field SqlBool)

Condition on which to join

-> Select (fieldsL, nullableFieldsR)

Left join

We suggest you use optionalRestrict instead. Instead of writing "leftJoin qL qR cond" you can write

proc () -> do
  fieldsL <- qL -< ()
  maybeFieldsR <- optionalRestrict qR -< curry cond fieldsL
  returnA -< (fieldsL, maybeFieldsR)

Typically everything except the optionalRestrict line can be inlined in surrounding arrow notation. In such cases, readability and maintainibility increase dramatically.

leftJoinA Source #

Arguments

:: (Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsR nullableFieldsR) 
=> Select fieldsR

Right query

-> SelectArr (fieldsR -> Field SqlBool) nullableFieldsR

Condition on which to join goes in, left join result comes out

We suggest you don't use this. optionalRestrict is probably better for your use case. leftJoinA is the same as optionalRestrict except without the return type wrapped in MaybeFields.

rightJoin Source #

Arguments

:: (Default Unpackspec fieldsL fieldsL, Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsL nullableFieldsL) 
=> Select fieldsL

Left query

-> Select fieldsR

Right query

-> ((fieldsL, fieldsR) -> Field SqlBool)

Condition on which to join

-> Select (nullableFieldsL, fieldsR)

Right join

We suggest you use optionalRestrict instead. See leftJoin for more details.

fullJoin Source #

Arguments

:: (Default Unpackspec fieldsL fieldsL, Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsL nullableFieldsL, Default NullMaker fieldsR nullableFieldsR) 
=> Select fieldsL

Left query

-> Select fieldsR

Right query

-> ((fieldsL, fieldsR) -> Field SqlBool)

Condition on which to join

-> Select (nullableFieldsL, nullableFieldsR)

Full outer join

leftJoinExplicit :: Unpackspec fieldsL fieldsL -> Unpackspec fieldsR fieldsR -> NullMaker fieldsR nullableFieldsR -> Select fieldsL -> Select fieldsR -> ((fieldsL, fieldsR) -> Field SqlBool) -> Select (fieldsL, nullableFieldsR) Source #

leftJoinAExplict :: Unpackspec fieldsR fieldsR -> NullMaker fieldsR nullableFieldsR -> Select fieldsR -> SelectArr (fieldsR -> Field SqlBool) nullableFieldsR Source #

rightJoinExplicit :: Unpackspec fieldsL fieldsL -> Unpackspec fieldsR fieldsR -> NullMaker fieldsL nullableFieldsL -> Select fieldsL -> Select fieldsR -> ((fieldsL, fieldsR) -> Field SqlBool) -> Select (nullableFieldsL, fieldsR) Source #

fullJoinExplicit :: Unpackspec fieldsL fieldsL -> Unpackspec fieldsR fieldsR -> NullMaker fieldsL nullableFieldsL -> NullMaker fieldsR nullableFieldsR -> Select fieldsL -> Select fieldsR -> ((fieldsL, fieldsR) -> Field SqlBool) -> Select (nullableFieldsL, nullableFieldsR) Source #

leftJoinInferrable Source #

Arguments

:: (Default Unpackspec fieldsL fieldsL, Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsR nullableFieldsR, Map Nulled fieldsR ~ nullableFieldsR) 
=> Select fieldsL

Left query

-> Select fieldsR

Right query

-> ((fieldsL, fieldsR) -> Field SqlBool)

Condition on which to join

-> Select (fieldsL, nullableFieldsR)

Left join

Deprecated: Use optionalRestrict instead.

rightJoinInferrable Source #

Arguments

:: (Default Unpackspec fieldsL fieldsL, Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsL nullableFieldsL, Map Nulled fieldsL ~ nullableFieldsL) 
=> Select fieldsL

Left query

-> Select fieldsR

Right query

-> ((fieldsL, fieldsR) -> Field SqlBool)

Condition on which to join

-> Select (nullableFieldsL, fieldsR)

Right join

Deprecated: Use optionalRestrict instead.

fullJoinInferrable Source #

Arguments

:: (Default Unpackspec fieldsL fieldsL, Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsL nullableFieldsL, Default NullMaker fieldsR nullableFieldsR, Map Nulled fieldsL ~ nullableFieldsL, Map Nulled fieldsR ~ nullableFieldsR) 
=> Select fieldsL

Left query

-> Select fieldsR

Right query

-> ((fieldsL, fieldsR) -> Field SqlBool)

Condition on which to join

-> Select (nullableFieldsL, nullableFieldsR)

Full outer join

Deprecated: Use rightJoinF instead.

data Nullspec fields fields' Source #

Instances

Instances details
Profunctor Nullspec Source # 
Instance details

Defined in Opaleye.Internal.Values

Methods

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

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

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

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

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

ProductProfunctor Nullspec Source # 
Instance details

Defined in Opaleye.Internal.Values

Methods

purePP :: b -> Nullspec a b #

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

empty :: Nullspec () () #

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

IsSqlType b => Default Nullspec a (Column b) Source # 
Instance details

Defined in Opaleye.Internal.Values

Methods

def :: Nullspec a (Column b) #

Functor (Nullspec a) Source # 
Instance details

Defined in Opaleye.Internal.Values

Methods

fmap :: (a0 -> b) -> Nullspec a a0 -> Nullspec a b #

(<$) :: a0 -> Nullspec a b -> Nullspec a a0 #

Applicative (Nullspec a) Source # 
Instance details

Defined in Opaleye.Internal.Values

Methods

pure :: a0 -> Nullspec a a0 #

(<*>) :: Nullspec a (a0 -> b) -> Nullspec a a0 -> Nullspec a b #

liftA2 :: (a0 -> b -> c) -> Nullspec a a0 -> Nullspec a b -> Nullspec a c #

(*>) :: Nullspec a a0 -> Nullspec a b -> Nullspec a b #

(<*) :: Nullspec a a0 -> Nullspec a b -> Nullspec a a0 #

data MaybeFields fields Source #

The Opaleye analogue of Maybe

Instances

Instances details
Monad MaybeFields Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Methods

(>>=) :: MaybeFields a -> (a -> MaybeFields b) -> MaybeFields b #

(>>) :: MaybeFields a -> MaybeFields b -> MaybeFields b #

return :: a -> MaybeFields a #

Functor MaybeFields Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Methods

fmap :: (a -> b) -> MaybeFields a -> MaybeFields b #

(<$) :: a -> MaybeFields b -> MaybeFields a #

Applicative MaybeFields Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Methods

pure :: a -> MaybeFields a #

(<*>) :: MaybeFields (a -> b) -> MaybeFields a -> MaybeFields b #

liftA2 :: (a -> b -> c) -> MaybeFields a -> MaybeFields b -> MaybeFields c #

(*>) :: MaybeFields a -> MaybeFields b -> MaybeFields b #

(<*) :: MaybeFields a -> MaybeFields b -> MaybeFields a #

Default Unpackspec a b => Default Unpackspec (MaybeFields a) (MaybeFields b) Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Default (WithNulls Binaryspec) a b => Default Binaryspec (MaybeFields a) (MaybeFields b) Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Default IfPP a b => Default IfPP (MaybeFields a) (MaybeFields b) Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Methods

def :: IfPP (MaybeFields a) (MaybeFields b) #

Default EqPP a b => Default EqPP (MaybeFields a) (MaybeFields b) Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Methods

def :: EqPP (MaybeFields a) (MaybeFields 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) #

Default Valuesspec a b => Default Valuesspec (MaybeFields a) (MaybeFields b) Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

(Default ToFields a b, Default Nullspec a b) => Default ToFields (Maybe a) (MaybeFields b) Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Methods

def :: ToFields (Maybe a) (MaybeFields b) #

Default (WithNulls Distinctspec) a b => Default Distinctspec (MaybeFields a) (MaybeFields b) Source # 
Instance details

Defined in Opaleye.Internal.Distinct

(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 #

nothingFields :: Default Nullspec a a => MaybeFields a Source #

The Opaleye analogue of Nothing.

nothingFieldsOfTypeOf :: a -> MaybeFields a Source #

The Opaleye analogue of const Nothing. Can be useful to avoid type inference problems, because it doesn't pick up a type class constraint.

justFields :: a -> MaybeFields a Source #

The Opaleye analogue of Just. Equivalent to pure.

maybeFields :: Default IfPP b b => b -> (a -> b) -> MaybeFields a -> b Source #

The Opaleye analogue of maybe

fromMaybeFields :: Default IfPP b b => b -> MaybeFields b -> b Source #

The Opaleye analogue of fromMaybe

catMaybeFields :: SelectArr i (MaybeFields a) -> SelectArr i a Source #

The Opaleye analogue of catMaybes

maybeFieldsExplicit :: IfPP b b' -> b -> (a -> b) -> MaybeFields a -> b' Source #

fromFieldsMaybeFields :: FromFields fields haskells -> FromFields (MaybeFields fields) (Maybe haskells) Source #

traverseMaybeFields Source #

Arguments

:: (Default Unpackspec a a, Default Unpackspec b b) 
=> SelectArr a b 
-> SelectArr (MaybeFields a) (MaybeFields b) 

traverseMaybeFields is analogous to Haskell's traverse :: (a -> [b]) -> Maybe a -> [Maybe b]. In particular, traverse has the following definition that generalises to traverseMaybeFields:

  • traverse _ Nothing = pure Nothing
  • traverse f (Just x) = fmap Just (f x)

data Cursor haskells Source #

Cursor within a transaction.

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

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 #

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

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

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]

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.

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.

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 #

runSelectI Source #

Arguments

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

Version of runSelect with better type inference