squeal-postgresql-0.9.1.3: Squeal PostgreSQL Library
Copyright(c) Eitan Chatav 2019
Maintainereitan@morphism.tech
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

Squeal.PostgreSQL.Expression.Range

Description

range types and functions

Synopsis

Range

data Range x Source #

A Range datatype that comprises connected subsets of the real line.

Constructors

Empty 
NonEmpty (Bound x) (Bound x) 

Instances

Instances details
Foldable Range Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Range

Methods

fold :: Monoid m => Range m -> m #

foldMap :: Monoid m => (a -> m) -> Range a -> m #

foldMap' :: Monoid m => (a -> m) -> Range a -> m #

foldr :: (a -> b -> b) -> b -> Range a -> b #

foldr' :: (a -> b -> b) -> b -> Range a -> b #

foldl :: (b -> a -> b) -> b -> Range a -> b #

foldl' :: (b -> a -> b) -> b -> Range a -> b #

foldr1 :: (a -> a -> a) -> Range a -> a #

foldl1 :: (a -> a -> a) -> Range a -> a #

toList :: Range a -> [a] #

null :: Range a -> Bool #

length :: Range a -> Int #

elem :: Eq a => a -> Range a -> Bool #

maximum :: Ord a => Range a -> a #

minimum :: Ord a => Range a -> a #

sum :: Num a => Range a -> a #

product :: Num a => Range a -> a #

Traversable Range Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Range

Methods

traverse :: Applicative f => (a -> f b) -> Range a -> f (Range b) #

sequenceA :: Applicative f => Range (f a) -> f (Range a) #

mapM :: Monad m => (a -> m b) -> Range a -> m (Range b) #

sequence :: Monad m => Range (m a) -> m (Range a) #

Functor Range Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Range

Methods

fmap :: (a -> b) -> Range a -> Range b #

(<$) :: a -> Range b -> Range a #

ToPG db x => ToPG db (Range x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

Generic (Range x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Range

Associated Types

type Rep (Range x) :: Type -> Type #

Methods

from :: Range x -> Rep (Range x) x0 #

to :: Rep (Range x) x0 -> Range x #

Read x => Read (Range x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Range

Show x => Show (Range x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Range

Methods

showsPrec :: Int -> Range x -> ShowS #

show :: Range x -> String #

showList :: [Range x] -> ShowS #

Generic (Range x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Range

Associated Types

type Code (Range x) :: [[Type]] #

Methods

from :: Range x -> Rep (Range x) #

to :: Rep (Range x) -> Range x #

HasDatatypeInfo (Range x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Range

Associated Types

type DatatypeInfoOf (Range x) :: DatatypeInfo #

Methods

datatypeInfo :: proxy (Range x) -> DatatypeInfo (Code (Range x)) #

Eq x => Eq (Range x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Range

Methods

(==) :: Range x -> Range x -> Bool #

(/=) :: Range x -> Range x -> Bool #

Ord x => Ord (Range x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Range

Methods

compare :: Range x -> Range x -> Ordering #

(<) :: Range x -> Range x -> Bool #

(<=) :: Range x -> Range x -> Bool #

(>) :: Range x -> Range x -> Bool #

(>=) :: Range x -> Range x -> Bool #

max :: Range x -> Range x -> Range x #

min :: Range x -> Range x -> Range x #

Inline (Range Int32) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Inline

Methods

inline :: forall (null :: PGType -> NullType). Range Int32 -> Expr (null (PG (Range Int32))) Source #

Inline (Range Int64) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Inline

Methods

inline :: forall (null :: PGType -> NullType). Range Int64 -> Expr (null (PG (Range Int64))) Source #

Inline (Range Scientific) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Inline

Methods

inline :: forall (null :: PGType -> NullType). Range Scientific -> Expr (null (PG (Range Scientific))) Source #

Inline (Range Day) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Inline

Methods

inline :: forall (null :: PGType -> NullType). Range Day -> Expr (null (PG (Range Day))) Source #

Inline (Range UTCTime) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Inline

Methods

inline :: forall (null :: PGType -> NullType). Range UTCTime -> Expr (null (PG (Range UTCTime))) Source #

Inline (Range LocalTime) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Inline

Methods

inline :: forall (null :: PGType -> NullType). Range LocalTime -> Expr (null (PG (Range LocalTime))) Source #

FromPG y => FromPG (Range y) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

IsPG hask => IsPG (Range hask) Source #

PGrange (PG hask)

Instance details

Defined in Squeal.PostgreSQL.Expression.Range

Associated Types

type PG (Range hask) :: PGType Source #

type Rep (Range x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Range

type Rep (Range x) = D1 ('MetaData "Range" "Squeal.PostgreSQL.Expression.Range" "squeal-postgresql-0.9.1.3-FfCgbPNg57H53ZAGizr3Nu" 'False) (C1 ('MetaCons "Empty" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NonEmpty" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Bound x)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Bound x))))
type Code (Range x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Range

type Code (Range x) = GCode (Range x)
type DatatypeInfoOf (Range x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Range

type PG (Range hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Range

type PG (Range hask) = 'PGrange (PG hask)

(<=..<=) :: x -> x -> Range x infix 4 Source #

Finite Range constructor

(<..<) :: x -> x -> Range x infix 4 Source #

Finite Range constructor

(<=..<) :: x -> x -> Range x infix 4 Source #

Finite Range constructor

(<..<=) :: x -> x -> Range x infix 4 Source #

Finite Range constructor

moreThan :: x -> Range x Source #

Half-infinite Range constructor

atLeast :: x -> Range x Source #

Half-infinite Range constructor

lessThan :: x -> Range x Source #

Half-infinite Range constructor

atMost :: x -> Range x Source #

Half-infinite Range constructor

singleton :: x -> Range x Source #

A point on the line

whole :: Range x Source #

The whole line

data Bound x Source #

The type of Bound for a Range.

Constructors

Infinite

unbounded

Closed x

inclusive

Open x

exclusive

Instances

Instances details
Foldable Bound Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Range

Methods

fold :: Monoid m => Bound m -> m #

foldMap :: Monoid m => (a -> m) -> Bound a -> m #

foldMap' :: Monoid m => (a -> m) -> Bound a -> m #

foldr :: (a -> b -> b) -> b -> Bound a -> b #

foldr' :: (a -> b -> b) -> b -> Bound a -> b #

foldl :: (b -> a -> b) -> b -> Bound a -> b #

foldl' :: (b -> a -> b) -> b -> Bound a -> b #

foldr1 :: (a -> a -> a) -> Bound a -> a #

foldl1 :: (a -> a -> a) -> Bound a -> a #

toList :: Bound a -> [a] #

null :: Bound a -> Bool #

length :: Bound a -> Int #

elem :: Eq a => a -> Bound a -> Bool #

maximum :: Ord a => Bound a -> a #

minimum :: Ord a => Bound a -> a #

sum :: Num a => Bound a -> a #

product :: Num a => Bound a -> a #

Traversable Bound Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Range

Methods

traverse :: Applicative f => (a -> f b) -> Bound a -> f (Bound b) #

sequenceA :: Applicative f => Bound (f a) -> f (Bound a) #

mapM :: Monad m => (a -> m b) -> Bound a -> m (Bound b) #

sequence :: Monad m => Bound (m a) -> m (Bound a) #

Functor Bound Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Range

Methods

fmap :: (a -> b) -> Bound a -> Bound b #

(<$) :: a -> Bound b -> Bound a #

Generic (Bound x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Range

Associated Types

type Rep (Bound x) :: Type -> Type #

Methods

from :: Bound x -> Rep (Bound x) x0 #

to :: Rep (Bound x) x0 -> Bound x #

Read x => Read (Bound x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Range

Show x => Show (Bound x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Range

Methods

showsPrec :: Int -> Bound x -> ShowS #

show :: Bound x -> String #

showList :: [Bound x] -> ShowS #

Eq x => Eq (Bound x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Range

Methods

(==) :: Bound x -> Bound x -> Bool #

(/=) :: Bound x -> Bound x -> Bool #

Ord x => Ord (Bound x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Range

Methods

compare :: Bound x -> Bound x -> Ordering #

(<) :: Bound x -> Bound x -> Bool #

(<=) :: Bound x -> Bound x -> Bool #

(>) :: Bound x -> Bound x -> Bool #

(>=) :: Bound x -> Bound x -> Bool #

max :: Bound x -> Bound x -> Bound x #

min :: Bound x -> Bound x -> Bound x #

type Rep (Bound x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Range

type Rep (Bound x) = D1 ('MetaData "Bound" "Squeal.PostgreSQL.Expression.Range" "squeal-postgresql-0.9.1.3-FfCgbPNg57H53ZAGizr3Nu" 'False) (C1 ('MetaCons "Infinite" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Closed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 x)) :+: C1 ('MetaCons "Open" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 x))))

Range Function

Range Construction

range Source #

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 (null0 ty) (null1 ('PGrange ty)) ('Null 'PGbool) Source #

range is contained by

(@>.) :: Operator (null0 ('PGrange ty)) (null1 ty) ('Null 'PGbool) Source #

contains range

(<<@) :: 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 #

intersection

(@-) :: 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

Range Function

lowerBound :: null ('PGrange ty) --> 'Null ty Source #

lower bound of range

upperBound :: null ('PGrange ty) --> 'Null ty Source #

upper bound of range

isEmpty :: null ('PGrange ty) --> 'Null 'PGbool Source #

is the range empty?

lowerInc :: null ('PGrange ty) --> 'Null 'PGbool Source #

is the lower bound inclusive?

lowerInf :: null ('PGrange ty) --> 'Null 'PGbool Source #

is the lower bound infinite?

upperInc :: null ('PGrange ty) --> 'Null 'PGbool Source #

is the upper bound inclusive?

upperInf :: null ('PGrange ty) --> 'Null 'PGbool Source #

is the upper bound infinite?

rangeMerge :: '[null ('PGrange ty), null ('PGrange ty)] ---> null ('PGrange ty) Source #

the smallest range which includes both of the given ranges