Safe Haskell | None |
---|---|
Language | Haskell2010 |
Module for creating filter conditions
Example as used in nested structure for scan:
scanCond (hashitem' <!:> "a" <.> author' <.> name' ==. "x") 20
- data FilterCondition t = Not (FilterCondition t)
- (&&.) :: FilterCondition t -> FilterCondition t -> FilterCondition t
- (||.) :: FilterCondition t -> FilterCondition t -> FilterCondition t
- (==.) :: (InCollection col tbl FullPath, DynamoEncodable typ) => Column typ ctyp col -> typ -> FilterCondition tbl
- (/=.) :: (InCollection col tbl FullPath, DynamoEncodable typ) => Column typ ctyp col -> typ -> FilterCondition tbl
- (>=.) :: (InCollection col tbl FullPath, DynamoEncodable typ, Ord typ) => Column typ ctyp col -> typ -> FilterCondition tbl
- (>.) :: (InCollection col tbl FullPath, DynamoEncodable typ, Ord typ) => Column typ ctyp col -> typ -> FilterCondition tbl
- (<=.) :: (InCollection col tbl FullPath, DynamoEncodable typ, Ord typ) => Column typ ctyp col -> typ -> FilterCondition tbl
- (<.) :: (InCollection col tbl FullPath, DynamoEncodable typ, Ord typ) => Column typ ctyp col -> typ -> FilterCondition tbl
- attrExists :: InCollection col tbl FullPath => Column typ TypColumn col -> FilterCondition tbl
- attrMissing :: InCollection col tbl FullPath => Column typ TypColumn col -> FilterCondition tbl
- beginsWith :: (InCollection col tbl FullPath, IsText typ) => Column typ TypColumn col -> Text -> FilterCondition tbl
- contains :: (InCollection col tbl FullPath, IsText typ) => Column typ TypColumn col -> Text -> FilterCondition tbl
- setContains :: (InCollection col tbl FullPath, DynamoScalar v a) => Column (Set a) TypColumn col -> a -> FilterCondition tbl
- valIn :: (InCollection col tbl FullPath, DynamoScalar v typ) => Column typ ctyp col -> [typ] -> FilterCondition tbl
- between :: (Ord typ, InCollection col tbl FullPath, DynamoScalar v typ) => Column typ ctyp col -> (typ, typ) -> FilterCondition tbl
- size :: Column typ TypColumn col -> Column Int TypSize col
Condition datatype
data FilterCondition t Source #
Filter condition. Use with scan, query, update and delete methods.
Filtering on primary key is not allowed.
Not (FilterCondition t) | Negate condition |
Logical operators
(&&.) :: FilterCondition t -> FilterCondition t -> FilterCondition t infixr 3 Source #
AND for combining conditions.
(||.) :: FilterCondition t -> FilterCondition t -> FilterCondition t infixr 3 Source #
OR for combining conditions
Equality comparisons
(==.) :: (InCollection col tbl FullPath, DynamoEncodable typ) => Column typ ctyp col -> typ -> FilterCondition tbl infix 4 Source #
Tests for equality. Automatically adjusts query to account for missing attributes.
Note: checks against empty values esentially translate to attrMissing
.
(/=.) :: (InCollection col tbl FullPath, DynamoEncodable typ) => Column typ ctyp col -> typ -> FilterCondition tbl infix 4 Source #
a /= b === Not (a == b)
(>=.) :: (InCollection col tbl FullPath, DynamoEncodable typ, Ord typ) => Column typ ctyp col -> typ -> FilterCondition tbl infix 4 Source #
(>.) :: (InCollection col tbl FullPath, DynamoEncodable typ, Ord typ) => Column typ ctyp col -> typ -> FilterCondition tbl infix 4 Source #
(<=.) :: (InCollection col tbl FullPath, DynamoEncodable typ, Ord typ) => Column typ ctyp col -> typ -> FilterCondition tbl infix 4 Source #
(<.) :: (InCollection col tbl FullPath, DynamoEncodable typ, Ord typ) => Column typ ctyp col -> typ -> FilterCondition tbl infix 4 Source #
Extended functions
attrExists :: InCollection col tbl FullPath => Column typ TypColumn col -> FilterCondition tbl Source #
Check existence of attribute.
attrMissing :: InCollection col tbl FullPath => Column typ TypColumn col -> FilterCondition tbl Source #
Checks non-existence of an attribute
beginsWith :: (InCollection col tbl FullPath, IsText typ) => Column typ TypColumn col -> Text -> FilterCondition tbl Source #
Comparison for text columns.
contains :: (InCollection col tbl FullPath, IsText typ) => Column typ TypColumn col -> Text -> FilterCondition tbl Source #
CONTAINS condition for text-like attributes.
setContains :: (InCollection col tbl FullPath, DynamoScalar v a) => Column (Set a) TypColumn col -> a -> FilterCondition tbl Source #
CONTAINS condition for sets.
valIn :: (InCollection col tbl FullPath, DynamoScalar v typ) => Column typ ctyp col -> [typ] -> FilterCondition tbl Source #
a IN (b, c, d); the list may contain up to 100 values.
between :: (Ord typ, InCollection col tbl FullPath, DynamoScalar v typ) => Column typ ctyp col -> (typ, typ) -> FilterCondition tbl Source #
Numeric/string range comparison.