opaleye-0.5.3.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 #

Restrict query results to a particular condition. Corresponds to the guard method of the MonadPlus class. You would typically use restrict if you want to use Arrow notation.

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

Filter a QueryArr to only those rows where the given condition holds. This is the QueryArr equivalent of filter from the Prelude. You would typically use keepWhen if you want to use a "point free" style.

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

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

Conditional operators

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 -> QueryArr () 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?

Other operators

doubleOfInt :: Column PGInt4 -> Column PGFloat8 Source #

Cast a PGInt4 to a PGFloat8