opaleye-0.7.1.0: An SQL-generating DSL targeting PostgreSQL

Safe HaskellNone
LanguageHaskell2010

Opaleye.Operators

Contents

Description

Operators on Columns. Please note that numeric Column types are instances of Num, so you can use *, /, +, - on them.

Synopsis

Restriction operators

where_ :: Field SqlBool -> Select () Source #

Keep only the rows of a query satisfying a given condition, using an SQL WHERE clause. It is equivalent to the Haskell function

where_ :: Bool -> [()]
where_ True  = [()]
where_ False = []

restrict :: SelectArr (Field SqlBool) () Source #

You would typically use restrict if you want to write your query using Arrow notation. If you want to use monadic style then where_ will suit you better.

restrictExists :: SelectArr a b -> SelectArr a () Source #

Add a WHERE EXISTS clause to the current query.

restrictNotExists :: SelectArr a b -> SelectArr a () Source #

Add a WHERE NOT EXISTS clause to the current query.

Equality operators

(.==) :: Column a -> Column a -> Field SqlBool infix 4 Source #

(./=) :: Column a -> Column a -> Field SqlBool infix 4 Source #

(.===) :: Default EqPP fields fields => fields -> fields -> Field SqlBool infix 4 Source #

A polymorphic equality operator that works for all types that you have run makeAdaptorAndInstance on. This may be unified with .== in a future version.

(./==) :: Default EqPP fields fields => fields -> fields -> Field SqlBool infix 4 Source #

A polymorphic inequality operator that works for all types that you have run makeAdaptorAndInstance on. This may be unified with ./= in a future version.

Comparison operators

(.>) :: SqlOrd a => Column a -> Column a -> Field SqlBool infix 4 Source #

(.<) :: SqlOrd a => Column a -> Column a -> Field SqlBool infix 4 Source #

(.<=) :: SqlOrd a => Column a -> Column a -> Field SqlBool infix 4 Source #

(.>=) :: SqlOrd a => Column a -> Column a -> Field SqlBool infix 4 Source #

Numerical operators

quot_ :: SqlIntegral a => Column a -> Column a -> Column a Source #

Integral division, named after quot. It maps to the / operator in Postgres.

rem_ :: SqlIntegral a => Column a -> Column a -> Column a Source #

The remainder of integral division, named after rem. It maps to MOD (%) in Postgres, confusingly described as "modulo (remainder)".

Conditional operators

case_ :: [(Field SqlBool, Column a)] -> Column a -> Column a Source #

Select the first case for which the condition is true.

ifThenElse :: Field SqlBool -> Column a -> Column a -> Column a Source #

Monomorphic if/then/else.

This may be replaced by ifThenElseMany in a future version.

ifThenElseMany :: Default IfPP fields fields => Field SqlBool -> fields -> fields -> fields Source #

Polymorphic if/then/else.

Logical operators

(.||) :: Field SqlBool -> Field SqlBool -> Field SqlBool infixr 2 Source #

Boolean or

(.&&) :: Field SqlBool -> Field SqlBool -> Field SqlBool infixr 3 Source #

Boolean and

not :: Field SqlBool -> Field SqlBool Source #

Boolean not

ors :: Foldable f => f (Field SqlBool) -> Field SqlBool Source #

True when any element of the container is true

Text operators

lower :: Field SqlText -> Field SqlText Source #

To lowercase

upper :: Field SqlText -> Field SqlText Source #

To uppercase

like :: Field SqlText -> Field SqlText -> Field SqlBool Source #

Postgres LIKE operator

ilike :: Field SqlText -> Field SqlText -> Field SqlBool Source #

Postgres ILIKE operator

charLength :: PGString a => Column a -> Column Int Source #

Do not use. Will be deprecated in 0.8. You probably want to use sqlLength instead.

Containment operators

in_ :: (Functor f, Foldable f) => f (Column a) -> Column a -> Field SqlBool Source #

in_ is designed to be used in prefix form.

in_ validProducts product checks whether product is a valid product. in_ validProducts is a function which checks whether a product is a valid product.

inSelect :: Default EqPP fields fields => fields -> Select fields -> Select (Field SqlBool) Source #

True if the first argument occurs amongst the rows of the second, false otherwise.

This operation is equivalent to Postgres's IN operator but, for expediency, is currently implemented using a LEFT JOIN. Please file a bug if this causes any issues in practice.

JSON operators

class SqlIsJson a Source #

Class of Postgres types that represent json values. Used to overload functions and operators that work on both SqlJson and SqlJsonb.

Warning: making additional instances of this class can lead to broken code!

Instances
SqlIsJson SqlJsonb Source # 
Instance details

Defined in Opaleye.Operators

SqlIsJson SqlJson Source # 
Instance details

Defined in Opaleye.Operators

type PGIsJson = SqlIsJson Source #

Deprecated: Use SqlIsJson instead

class SqlJsonIndex a Source #

Class of Postgres types that can be used to index json values.

Warning: making additional instances of this class can lead to broken code!

Instances
SqlJsonIndex SqlText Source # 
Instance details

Defined in Opaleye.Operators

SqlJsonIndex SqlInt4 Source # 
Instance details

Defined in Opaleye.Operators

SqlJsonIndex SqlInt8 Source # 
Instance details

Defined in Opaleye.Operators

(.->) infixl 8 Source #

Arguments

:: (SqlIsJson a, SqlJsonIndex k) 
=> FieldNullable a 
-> Field k

key or index

-> FieldNullable a 

Get JSON object field by key.

(.->>) infixl 8 Source #

Arguments

:: (SqlIsJson a, SqlJsonIndex k) 
=> FieldNullable a 
-> Field k

key or index

-> FieldNullable SqlText 

Get JSON object field as text.

(.#>) infixl 8 Source #

Arguments

:: SqlIsJson a 
=> FieldNullable a 
-> Column (SqlArray SqlText)

path

-> FieldNullable a 

Get JSON object at specified path.

(.#>>) infixl 8 Source #

Get JSON object at specified path as text.

(.@>) :: Field SqlJsonb -> Field SqlJsonb -> Field SqlBool infix 4 Source #

Does the left JSON value contain within it the right value?

(.<@) :: Field SqlJsonb -> Field SqlJsonb -> Field SqlBool infix 4 Source #

Is the left JSON value contained within the right value?

(.?) :: Field SqlJsonb -> Field SqlText -> Field SqlBool infix 4 Source #

Does the key/element string exist within the JSON value?

(.?|) :: Field SqlJsonb -> Column (SqlArray SqlText) -> Field SqlBool infix 4 Source #

Do any of these key/element strings exist?

(.?&) :: Field SqlJsonb -> Column (SqlArray SqlText) -> Field SqlBool infix 4 Source #

Do all of these key/element strings exist?

SqlArray operators

arrayPrepend :: Column a -> Column (SqlArray a) -> Column (SqlArray a) Source #

Prepend an element to a SqlArray

arrayRemove :: Column a -> Column (SqlArray a) -> Column (SqlArray a) Source #

Remove all instances of an element from a SqlArray

arrayRemoveNulls :: Column (SqlArray (Nullable a)) -> Column (SqlArray a) Source #

Remove all NULL values from a SqlArray

Range operators

upperBound :: IsRangeType a => Column (SqlRange a) -> Column (Nullable a) Source #

Access the upper bound of a range. For discrete range types it is the exclusive bound.

lowerBound :: IsRangeType a => Column (SqlRange a) -> Column (Nullable a) Source #

Access the lower bound of a range. For discrete range types it is the inclusive bound.

Other operators

Deprecated

exists :: QueryArr a b -> QueryArr a () Source #

Deprecated: Identical to restrictExists. Will be removed in version 0.8.

notExists :: QueryArr a b -> QueryArr a () Source #

Deprecated: Identical to restrictNotExists. Will be removed in version 0.8.

inQuery :: Default EqPP fields fields => fields -> Query fields -> Select (Field SqlBool) Source #

Deprecated: Identical to inSelect. Will be removed in version 0.8.

keepWhen :: (a -> Field SqlBool) -> SelectArr a a Source #

This function is probably not useful and is likely to be deprecated in the future.

Keep only the rows of a query satisfying a given condition, using an SQL WHERE clause.

You would typically use keepWhen if you want to write your query using a "point free" style. If you want to use Arrow notation then restrict will suit you better.

This is the SelectArr equivalent of filter from the Prelude.