Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- where_ :: Field SqlBool -> Select ()
- restrict :: SelectArr (Field SqlBool) ()
- restrictExists :: SelectArr a b -> SelectArr a ()
- restrictNotExists :: SelectArr a b -> SelectArr a ()
- (.==) :: Column a -> Column a -> Field SqlBool
- (./=) :: Column a -> Column a -> Field SqlBool
- (.===) :: Default EqPP fields fields => fields -> fields -> Field SqlBool
- (./==) :: Default EqPP fields fields => fields -> fields -> Field SqlBool
- (.>) :: SqlOrd a => Column a -> Column a -> Field SqlBool
- (.<) :: SqlOrd a => Column a -> Column a -> Field SqlBool
- (.<=) :: SqlOrd a => Column a -> Column a -> Field SqlBool
- (.>=) :: SqlOrd a => Column a -> Column a -> Field SqlBool
- quot_ :: SqlIntegral a => Column a -> Column a -> Column a
- rem_ :: SqlIntegral a => Column a -> Column a -> Column a
- case_ :: [(Field SqlBool, Column a)] -> Column a -> Column a
- ifThenElse :: Field SqlBool -> Column a -> Column a -> Column a
- ifThenElseMany :: Default IfPP fields fields => Field SqlBool -> fields -> fields -> fields
- (.||) :: Field SqlBool -> Field SqlBool -> Field SqlBool
- (.&&) :: Field SqlBool -> Field SqlBool -> Field SqlBool
- not :: Field SqlBool -> Field SqlBool
- ors :: Foldable f => f (Field SqlBool) -> Field SqlBool
- (.++) :: Field SqlText -> Field SqlText -> Field SqlText
- lower :: Field SqlText -> Field SqlText
- upper :: Field SqlText -> Field SqlText
- like :: Field SqlText -> Field SqlText -> Field SqlBool
- ilike :: Field SqlText -> Field SqlText -> Field SqlBool
- charLength :: PGString a => Column a -> Column Int
- sqlLength :: PGString a => Field a -> Field SqlInt4
- in_ :: (Functor f, Foldable f) => f (Column a) -> Column a -> Field SqlBool
- inSelect :: Default EqPP fields fields => fields -> Select fields -> Select (Field SqlBool)
- class SqlIsJson a
- type PGIsJson = SqlIsJson
- class SqlJsonIndex a
- type PGJsonIndex = SqlJsonIndex
- (.->) :: (SqlIsJson a, SqlJsonIndex k) => FieldNullable a -> Field k -> FieldNullable a
- (.->>) :: (SqlIsJson a, SqlJsonIndex k) => FieldNullable a -> Field k -> FieldNullable SqlText
- (.#>) :: SqlIsJson a => FieldNullable a -> Column (SqlArray SqlText) -> FieldNullable a
- (.#>>) :: SqlIsJson a => FieldNullable a -> Column (SqlArray SqlText) -> FieldNullable SqlText
- (.@>) :: Field SqlJsonb -> Field SqlJsonb -> Field SqlBool
- (.<@) :: Field SqlJsonb -> Field SqlJsonb -> Field SqlBool
- (.?) :: Field SqlJsonb -> Field SqlText -> Field SqlBool
- (.?|) :: Field SqlJsonb -> Column (SqlArray SqlText) -> Field SqlBool
- (.?&) :: Field SqlJsonb -> Column (SqlArray SqlText) -> Field SqlBool
- emptyArray :: IsSqlType a => Column (SqlArray a)
- arrayAppend :: Field (SqlArray a) -> Field (SqlArray a) -> Field (SqlArray a)
- arrayPrepend :: Column a -> Column (SqlArray a) -> Column (SqlArray a)
- arrayRemove :: Column a -> Column (SqlArray a) -> Column (SqlArray a)
- arrayRemoveNulls :: Column (SqlArray (Nullable a)) -> Column (SqlArray a)
- singletonArray :: IsSqlType a => Column a -> Column (SqlArray a)
- index :: SqlIntegral n => Column (SqlArray a) -> Column n -> Column (Nullable a)
- overlap :: Column (SqlRange a) -> Column (SqlRange a) -> Field SqlBool
- liesWithin :: IsRangeType a => Column a -> Column (SqlRange a) -> Field SqlBool
- upperBound :: IsRangeType a => Column (SqlRange a) -> Column (Nullable a)
- lowerBound :: IsRangeType a => Column (SqlRange a) -> Column (Nullable a)
- (.<<) :: Column (SqlRange a) -> Column (SqlRange a) -> Field SqlBool
- (.>>) :: Column (SqlRange a) -> Column (SqlRange a) -> Field SqlBool
- (.&<) :: Column (SqlRange a) -> Column (SqlRange a) -> Field SqlBool
- (.&>) :: Column (SqlRange a) -> Column (SqlRange a) -> Field SqlBool
- (.-|-) :: Column (SqlRange a) -> Column (SqlRange a) -> Field SqlBool
- timestamptzAtTimeZone :: Field SqlTimestamptz -> Field SqlText -> Field SqlTimestamp
- dateOfTimestamp :: Field SqlTimestamp -> Field SqlDate
- exists :: QueryArr a b -> QueryArr a ()
- notExists :: QueryArr a b -> QueryArr a ()
- inQuery :: Default EqPP fields fields => fields -> Query fields -> Select (Field SqlBool)
- keepWhen :: (a -> Field SqlBool) -> SelectArr a a
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 = []
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
(.===) :: 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
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
ors :: Foldable f => f (Field SqlBool) -> Field SqlBool Source #
True when any element of the container is true
Text operators
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
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 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 # | |
Defined in Opaleye.Operators | |
SqlIsJson SqlJson Source # | |
Defined in Opaleye.Operators |
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 # | |
Defined in Opaleye.Operators | |
SqlJsonIndex SqlInt4 Source # | |
Defined in Opaleye.Operators | |
SqlJsonIndex SqlInt8 Source # | |
Defined in Opaleye.Operators |
type PGJsonIndex = SqlJsonIndex Source #
:: (SqlIsJson a, SqlJsonIndex k) | |
=> FieldNullable a | |
-> Field k | key or index |
-> FieldNullable a |
Get JSON object field by key.
:: (SqlIsJson a, SqlJsonIndex k) | |
=> FieldNullable a | |
-> Field k | key or index |
-> FieldNullable SqlText |
Get JSON object field as text.
:: SqlIsJson a | |
=> FieldNullable a | |
-> Column (SqlArray SqlText) | path |
-> FieldNullable a |
Get JSON object at specified path.
:: SqlIsJson a | |
=> FieldNullable a | |
-> Column (SqlArray SqlText) | path |
-> FieldNullable SqlText |
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
arrayAppend :: Field (SqlArray a) -> Field (SqlArray a) -> Field (SqlArray a) Source #
Append two SqlArray
s
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
liesWithin :: IsRangeType a => Column a -> Column (SqlRange a) -> Field SqlBool Source #
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
.