opaleye-0.6.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

restrict :: QueryArr (Column PGBool) () Source #

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

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

(If you are familiar with MonadPlus or Alternative it may help you to know that restrict corresponds to the guard function.)

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

Add a WHERE EXISTS clause to the current query.

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

Add a WHERE NOT EXISTS clause to the current query.

keepWhen :: (a -> Column PGBool) -> QueryArr a a Source #

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 QueryArr equivalent of filter from the Prelude.

Equality operators

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

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

(.===) :: Default EqPP columns columns => columns -> columns -> Column PGBool 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 columns columns => columns -> columns -> Column PGBool 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

(.>) :: PGOrd a => Column a -> Column a -> Column PGBool infix 4 Source #

(.<) :: PGOrd a => Column a -> Column a -> Column PGBool infix 4 Source #

(.<=) :: PGOrd a => Column a -> Column a -> Column PGBool infix 4 Source #

(.>=) :: PGOrd a => Column a -> Column a -> Column PGBool infix 4 Source #

Numerical operators

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

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

rem_ :: PGIntegral 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_ :: [(Column PGBool, Column a)] -> Column a -> Column a Source #

Select the first case for which the condition is true.

ifThenElse :: Column PGBool -> Column a -> Column a -> Column a Source #

Monomorphic if/then/else.

This may be replaced by ifThenElseMany in a future version.

ifThenElseMany :: Default IfPP columns columns => Column PGBool -> columns -> columns -> columns Source #

Polymorphic if/then/else.

Logical operators

(.||) :: Column PGBool -> Column PGBool -> Column PGBool infixr 2 Source #

Boolean or

(.&&) :: Column PGBool -> Column PGBool -> Column PGBool infixr 3 Source #

Boolean and

not :: Column PGBool -> Column PGBool Source #

Boolean not

ors :: Foldable f => f (Column PGBool) -> Column PGBool Source #

True when any element of the container is true

Text operators

lower :: Column PGText -> Column PGText Source #

To lowercase

upper :: Column PGText -> Column PGText Source #

To uppercase

like :: Column PGText -> Column PGText -> Column PGBool Source #

Postgres LIKE operator

ilike :: Column PGText -> Column PGText -> Column PGBool Source #

Postgres ILIKE operator

Containment operators

in_ :: (Functor f, Foldable f) => f (Column a) -> Column a -> Column PGBool 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.

inQuery :: Default EqPP columns columns => columns -> Query columns -> Query (Column PGBool) 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 PGIsJson a Source #

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

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

class PGJsonIndex 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!

(.->) infixl 8 Source #

Arguments

:: (PGIsJson a, PGJsonIndex k) 
=> Column (Nullable a) 
-> Column k

key or index

-> Column (Nullable a) 

Get JSON object field by key.

(.->>) infixl 8 Source #

Arguments

:: (PGIsJson a, PGJsonIndex k) 
=> Column (Nullable a) 
-> Column k

key or index

-> Column (Nullable PGText) 

Get JSON object field as text.

(.#>) infixl 8 Source #

Arguments

:: PGIsJson a 
=> Column (Nullable a) 
-> Column (PGArray PGText)

path

-> Column (Nullable a) 

Get JSON object at specified path.

(.#>>) infixl 8 Source #

Arguments

:: PGIsJson a 
=> Column (Nullable a) 
-> Column (PGArray PGText)

path

-> Column (Nullable PGText) 

Get JSON object at specified path as text.

(.@>) :: Column PGJsonb -> Column PGJsonb -> Column PGBool infix 4 Source #

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

(.<@) :: Column PGJsonb -> Column PGJsonb -> Column PGBool infix 4 Source #

Is the left JSON value contained within the right value?

(.?) :: Column PGJsonb -> Column PGText -> Column PGBool infix 4 Source #

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

(.?|) :: Column PGJsonb -> Column (PGArray PGText) -> Column PGBool infix 4 Source #

Do any of these key/element strings exist?

(.?&) :: Column PGJsonb -> Column (PGArray PGText) -> Column PGBool infix 4 Source #

Do all of these key/element strings exist?

PGArray operators

Range operators

Other operators

Deprecated

doubleOfInt :: Column PGInt4 -> Column PGFloat8 Source #

Deprecated: Use unsafeCast instead. Will be removed in version 0.7.

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

Identical to restrictExists. Will be deprecated in version 0.7.

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

Identical to restrictNotExists. Will be deprecated in version 0.7.