| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Opaleye.Operators
Description
- restrict :: QueryArr (Column PGBool) ()
 - keepWhen :: (a -> Column PGBool) -> QueryArr a a
 - (.==) :: Column a -> Column a -> Column PGBool
 - (./=) :: Column a -> Column a -> Column PGBool
 - (.===) :: Default EqPP columns columns => columns -> columns -> Column PGBool
 - (./==) :: Default EqPP columns columns => columns -> columns -> Column PGBool
 - (.>) :: PGOrd a => Column a -> Column a -> Column PGBool
 - (.<) :: PGOrd a => Column a -> Column a -> Column PGBool
 - (.<=) :: PGOrd a => Column a -> Column a -> Column PGBool
 - (.>=) :: PGOrd a => Column a -> Column a -> Column PGBool
 - quot_ :: PGIntegral a => Column a -> Column a -> Column a
 - rem_ :: PGIntegral a => Column a -> Column a -> Column a
 - case_ :: [(Column PGBool, Column a)] -> Column a -> Column a
 - ifThenElse :: Column PGBool -> Column a -> Column a -> Column a
 - (.||) :: Column PGBool -> Column PGBool -> Column PGBool
 - not :: Column PGBool -> Column PGBool
 - (.++) :: Column PGText -> Column PGText -> Column PGText
 - lower :: Column PGText -> Column PGText
 - upper :: Column PGText -> Column PGText
 - like :: Column PGText -> Column PGText -> Column PGBool
 - charLength :: PGString a => Column a -> Column Int
 - ors :: Foldable f => f (Column PGBool) -> Column PGBool
 - in_ :: (Functor f, Foldable f) => f (Column a) -> Column a -> Column PGBool
 - inQuery :: Default EqPP columns columns => columns -> QueryArr () columns -> Query (Column PGBool)
 - timestamptzAtTimeZone :: Column PGTimestamptz -> Column PGText -> Column PGTimestamp
 - emptyArray :: IsSqlType a => Column (PGArray a)
 - arrayPrepend :: Column a -> Column (PGArray a) -> Column (PGArray a)
 - singletonArray :: IsSqlType a => Column a -> Column (PGArray a)
 - class PGIsJson a
 - class PGJsonIndex a
 - (.->) :: (PGIsJson a, PGJsonIndex k) => Column (Nullable a) -> Column k -> Column (Nullable a)
 - (.->>) :: (PGIsJson a, PGJsonIndex k) => Column (Nullable a) -> Column k -> Column (Nullable PGText)
 - (.#>) :: PGIsJson a => Column (Nullable a) -> Column (PGArray PGText) -> Column (Nullable a)
 - (.#>>) :: PGIsJson a => Column (Nullable a) -> Column (PGArray PGText) -> Column (Nullable PGText)
 - (.@>) :: Column PGJsonb -> Column PGJsonb -> Column PGBool
 - (.<@) :: Column PGJsonb -> Column PGJsonb -> Column PGBool
 - (.?) :: Column PGJsonb -> Column PGText -> Column PGBool
 - (.?|) :: Column PGJsonb -> Column (PGArray PGText) -> Column PGBool
 - (.?&) :: Column PGJsonb -> Column (PGArray PGText) -> Column PGBool
 - doubleOfInt :: Column PGInt4 -> Column PGFloat8
 - (.&&) :: Column PGBool -> Column PGBool -> Column PGBool
 
Documentation
(.===) :: 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.
ors :: Foldable f => f (Column PGBool) -> Column PGBool Source #
True when any element of the container is true
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.
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!
Instances
Arguments
| :: (PGIsJson a, PGJsonIndex k) | |
| => Column (Nullable a) | |
| -> Column k | key or index  | 
| -> Column (Nullable a) | 
Get JSON object field by key.
Arguments
| :: (PGIsJson a, PGJsonIndex k) | |
| => Column (Nullable a) | |
| -> Column k | key or index  | 
| -> Column (Nullable PGText) | 
Get JSON object field as text.
Get JSON object at specified path.
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?