| Copyright | (c) Eitan Chatav 2019 |
|---|---|
| Maintainer | eitan@morphism.tech |
| Stability | experimental |
| Safe Haskell | None |
| Language | Haskell2010 |
Squeal.PostgreSQL.Expression.Range
Description
range types and functions
Synopsis
- data Range x
- (<=..<=) :: x -> x -> Range x
- (<..<) :: x -> x -> Range x
- (<=..<) :: x -> x -> Range x
- (<..<=) :: x -> x -> Range x
- moreThan :: x -> Range x
- atLeast :: x -> Range x
- lessThan :: x -> Range x
- atMost :: x -> Range x
- singleton :: x -> Range x
- whole :: Range x
- data Bound x
- range :: TypeExpression db (null (PGrange ty)) -> Range (Expression grp lat with db params from (NotNull ty)) -> Expression grp lat with db params from (null (PGrange ty))
- (.<@) :: Operator (NotNull ty) (null (PGrange ty)) (Null PGbool)
- (@>.) :: Operator (null (PGrange ty)) (NotNull ty) (Null PGbool)
- (<<@) :: Operator (null (PGrange ty)) (null (PGrange ty)) (Null PGbool)
- (@>>) :: Operator (null (PGrange ty)) (null (PGrange ty)) (Null PGbool)
- (&<) :: Operator (null (PGrange ty)) (null (PGrange ty)) (Null PGbool)
- (&>) :: Operator (null (PGrange ty)) (null (PGrange ty)) (Null PGbool)
- (-|-) :: Operator (null (PGrange ty)) (null (PGrange ty)) (Null PGbool)
- (@+) :: Operator (null (PGrange ty)) (null (PGrange ty)) (null (PGrange ty))
- (@*) :: Operator (null (PGrange ty)) (null (PGrange ty)) (null (PGrange ty))
- (@-) :: Operator (null (PGrange ty)) (null (PGrange ty)) (null (PGrange ty))
- lowerBound :: null (PGrange ty) --> Null ty
- upperBound :: null (PGrange ty) --> Null ty
- isEmpty :: null (PGrange ty) --> Null PGbool
- lowerInc :: null (PGrange ty) --> Null PGbool
- lowerInf :: null (PGrange ty) --> Null PGbool
- upperInc :: null (PGrange ty) --> Null PGbool
- upperInf :: null (PGrange ty) --> Null PGbool
- rangeMerge :: '[null (PGrange ty), null (PGrange ty)] ---> null (PGrange ty)
Range
A Range datatype that comprises connected subsets of
the real line.
Instances
Instances
Range Function
Range Construction
Arguments
| :: TypeExpression db (null (PGrange ty)) | range type |
| -> Range (Expression grp lat with db params from (NotNull ty)) | range of values |
| -> Expression grp lat with db params from (null (PGrange ty)) |
Construct a range
>>>printSQL $ range tstzrange (atLeast now)tstzrange(now(), NULL, '[)')>>>printSQL $ range numrange (0 <=..< 2*pi)numrange((0.0 :: numeric), ((2.0 :: numeric) * pi()), '[)')>>>printSQL $ range int4range Empty('empty' :: int4range)
Range Operator
(<<@) :: Operator (null (PGrange ty)) (null (PGrange ty)) (Null PGbool) Source #
strictly left of, return false when an empty range is involved
(@>>) :: Operator (null (PGrange ty)) (null (PGrange ty)) (Null PGbool) Source #
strictly right of, return false when an empty range is involved
(&<) :: Operator (null (PGrange ty)) (null (PGrange ty)) (Null PGbool) Source #
does not extend to the right of, return false when an empty range is involved
(&>) :: Operator (null (PGrange ty)) (null (PGrange ty)) (Null PGbool) Source #
does not extend to the left of, return false when an empty range is involved
(-|-) :: Operator (null (PGrange ty)) (null (PGrange ty)) (Null PGbool) Source #
is adjacent to, return false when an empty range is involved
(@+) :: Operator (null (PGrange ty)) (null (PGrange ty)) (null (PGrange ty)) Source #
union, will fail if the resulting range would need to contain two disjoint sub-ranges
(@-) :: Operator (null (PGrange ty)) (null (PGrange ty)) (null (PGrange ty)) Source #
difference, will fail if the resulting range would need to contain two disjoint sub-ranges