Copyright | (c) Eitan Chatav 2019 |
---|---|
Maintainer | eitan@morphism.tech |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
array functions
Synopsis
- array :: [Expression grp lat with db params from ty] -> Expression grp lat with db params from (null ('PGvararray ty))
- array0 :: TypeExpression db ty -> Expression grp lat with db params from (null ('PGvararray ty))
- array1 :: (n ~ Length tys, All ((~) ty) tys) => NP (Expression grp lat with db params from) tys -> Expression grp lat with db params from (null ('PGfixarray '[n] ty))
- array2 :: (All ((~) tys) tyss, All SListI tyss, Length tyss ~ n1, All ((~) ty) tys, Length tys ~ n2) => NP (NP (Expression grp lat with db params from)) tyss -> Expression grp lat with db params from (null ('PGfixarray '[n1, n2] ty))
- cardinality :: null ('PGvararray ty) --> null 'PGint8
- index :: Word64 -> null ('PGvararray ty) --> NullifyType ty
- index1 :: forall i n ty. (1 <= i, i <= n, KnownNat i) => 'NotNull ('PGfixarray '[n] ty) --> ty
- index2 :: forall i j m n ty. (1 <= i, i <= m, KnownNat i, 1 <= j, j <= n, KnownNat j) => 'NotNull ('PGfixarray '[m, n] ty) --> ty
- unnest :: null ('PGvararray ty) -|-> ("unnest" ::: '["unnest" ::: ty])
- arrAny :: Expression grp lat with db params from ty1 -> Operator ty1 ty2 ('Null 'PGbool) -> Expression grp lat with db params from (null ('PGvararray ty2)) -> Condition grp lat with db params from
- arrAll :: Expression grp lat with db params from ty1 -> Operator ty1 ty2 ('Null 'PGbool) -> Expression grp lat with db params from (null ('PGvararray ty2)) -> Condition grp lat with db params from
Array Functions
:: [Expression grp lat with db params from ty] | array elements |
-> Expression grp lat with db params from (null ('PGvararray ty)) |
Construct an array.
>>>
printSQL $ array [null_, false, true]
ARRAY[NULL, FALSE, TRUE]
array0 :: TypeExpression db ty -> Expression grp lat with db params from (null ('PGvararray ty)) Source #
Safely construct an empty array.
>>>
printSQL $ array0 text
(ARRAY[] :: text[])
:: (n ~ Length tys, All ((~) ty) tys) | |
=> NP (Expression grp lat with db params from) tys | array elements |
-> Expression grp lat with db params from (null ('PGfixarray '[n] ty)) |
Construct a fixed length array.
>>>
printSQL $ array1 (null_ :* false *: true)
ARRAY[NULL, FALSE, TRUE]
>>>
:type array1 (null_ :* false *: true)
array1 (null_ :* false *: true) :: Expression grp lat with db params from (null ('PGfixarray '[3] ('Null 'PGbool)))
:: (All ((~) tys) tyss, All SListI tyss, Length tyss ~ n1, All ((~) ty) tys, Length tys ~ n2) | |
=> NP (NP (Expression grp lat with db params from)) tyss | matrix elements |
-> Expression grp lat with db params from (null ('PGfixarray '[n1, n2] ty)) |
Construct a fixed size matrix.
>>>
printSQL $ array2 ((null_ :* false *: true) *: (false :* null_ *: true))
ARRAY[[NULL, FALSE, TRUE], [FALSE, NULL, TRUE]]
>>>
:type array2 ((null_ :* false *: true) *: (false :* null_ *: true))
array2 ((null_ :* false *: true) *: (false :* null_ *: true)) :: Expression grp lat with db params from (null ('PGfixarray '[2, 3] ('Null 'PGbool)))
cardinality :: null ('PGvararray ty) --> null 'PGint8 Source #
>>>
printSQL $ cardinality (array [null_, false, true])
cardinality(ARRAY[NULL, FALSE, TRUE])
:: Word64 | index |
-> null ('PGvararray ty) --> NullifyType ty |
>>>
printSQL $ array [null_, false, true] & index 2
(ARRAY[NULL, FALSE, TRUE])[2]
Typesafe indexing of fixed length arrays.
>>>
printSQL $ array1 (true *: false) & index1 @1
(ARRAY[TRUE, FALSE])[1]
:: forall i j m n ty. (1 <= i, i <= m, KnownNat i, 1 <= j, j <= n, KnownNat j) | |
=> 'NotNull ('PGfixarray '[m, n] ty) --> ty | matrix index |
Typesafe indexing of fixed size matrices.
>>>
printSQL $ array2 ((true *: false) *: (false *: true)) & index2 @1 @2
(ARRAY[[TRUE, FALSE], [FALSE, TRUE]])[1][2]
unnest :: null ('PGvararray ty) -|-> ("unnest" ::: '["unnest" ::: ty]) Source #
Expand an array to a set of rows
>>>
printSQL $ unnest (array [null_, false, true])
unnest(ARRAY[NULL, FALSE, TRUE])
:: Expression grp lat with db params from ty1 | expression |
-> Operator ty1 ty2 ('Null 'PGbool) | operator |
-> Expression grp lat with db params from (null ('PGvararray ty2)) | array |
-> Condition grp lat with db params from |
The right-hand side is a parenthesized expression, which must yield an array
value. The left-hand expression is evaluated and compared to each element of
the array using the given Operator
, which must yield a Boolean result. The
result of arrAny
is true
if any true result is obtained. The result is
false
if no true result is found (including the case where the array
has zero elements).
If the array expression yields a null array, the result of arrAny
will
be null. If the left-hand expression yields null, the result of arrAny
is
ordinarily null (though a non-strict comparison Operator
could possibly
yield a different result). Also, if the right-hand array contains any
null elements and no true comparison result is obtained, the result of
arrAny
will be null, not false
(again, assuming a strict comparison Operator
).
This is in accordance with SQL's normal rules for
Boolean combinations of null values.
>>>
printSQL $ arrAny true (.==) (array [true, false, null_])
(TRUE = ANY (ARRAY[TRUE, FALSE, NULL]))>>>
printSQL $ arrAny "hi" like (array ["bi","hi"])
((E'hi' :: text) LIKE ANY (ARRAY[(E'bi' :: text), (E'hi' :: text)]))
:: Expression grp lat with db params from ty1 | expression |
-> Operator ty1 ty2 ('Null 'PGbool) | operator |
-> Expression grp lat with db params from (null ('PGvararray ty2)) | array |
-> Condition grp lat with db params from |
The right-hand side is a parenthesized expression,
which must yield an array value. The left-hand expression
is evaluated and compared to each element of the array using
the given Operator
, which must yield a Boolean result.
The result of arrAll
is true
if all comparisons yield true
(including the case where the array has zero elements).
The result is false
if any false result is found.
If the array expression yields a null array,
the result of arrAll
will be null. If the left-hand expression yields null,
the result of arrAll
is ordinarily null
(though a non-strict comparison Operator
could possibly yield a different result).
Also, if the right-hand array contains any null
elements and no false comparison result is obtained,
the result of arrAll
will be null, not true
(again, assuming a strict comparison Operator
).
This is in accordance with SQL's normal rules for Boolean
combinations of null values.
>>>
printSQL $ arrAll true (.==) (array [true, false, null_])
(TRUE = ALL (ARRAY[TRUE, FALSE, NULL]))>>>
printSQL $ arrAll "hi" like (array ["bi","hi"])
((E'hi' :: text) LIKE ALL (ARRAY[(E'bi' :: text), (E'hi' :: text)]))