Copyright | 2015 Dylan Simon |
---|---|
Safe Haskell | None |
Language | Haskell98 |
Database.PostgreSQL.Typed.Range
Description
Representaion of PostgreSQL's range type. There are a number of existing range data types, but PostgreSQL's is rather particular. This tries to provide a one-to-one mapping.
- data Bound a
- newtype LowerBound a = Lower (Bound a)
- newtype UpperBound a = Upper (Bound a)
- data Range a
- = Empty
- | Range (LowerBound a) (UpperBound a)
- bound :: Bound a -> Maybe a
- boundClosed :: Bound a -> Bool
- makeBound :: Bool -> Maybe a -> Bound a
- lowerClosed :: Range a -> Bool
- upperClosed :: Range a -> Bool
- isEmpty :: Ord a => Range a -> Bool
- full :: Range a
- isFull :: Range a -> Bool
- point :: Eq a => a -> Range a
- getPoint :: Eq a => Range a -> Maybe a
- range :: Ord a => Bound a -> Bound a -> Range a
- normal :: Ord a => Maybe a -> Maybe a -> Range a
- bounded :: Ord a => a -> a -> Range a
- normalize :: Ord a => Range a -> Range a
- normalize' :: (Ord a, Enum a) => Range a -> Range a
- (@>) :: Ord a => Range a -> Range a -> Bool
- (<@) :: Ord a => Range a -> Range a -> Bool
- (@>.) :: Ord a => Range a -> a -> Bool
- intersect :: Ord a => Range a -> Range a -> Range a
- class (PGType tr, PGType t) => PGRangeType tr t | tr -> t where
- pgRangeElementType :: PGTypeName tr -> PGTypeName t
Documentation
newtype LowerBound a Source
Instances
Functor LowerBound | |
Eq a => Eq (LowerBound a) | |
Ord a => Ord (LowerBound a) |
newtype UpperBound a Source
Instances
Functor UpperBound | |
Eq a => Eq (UpperBound a) | |
Ord a => Ord (UpperBound a) |
Constructors
Empty | |
Range (LowerBound a) (UpperBound a) |
Instances
Functor Range | |
(PGRangeType tr t, PGColumn t a) => PGColumn tr (Range a) | |
(PGRangeType tr t, PGParameter t a) => PGParameter tr (Range a) | |
Eq a => Eq (Range a) | |
Show a => Show (Range a) |
boundClosed :: Bound a -> Bool Source
lowerClosed :: Range a -> Bool Source
upperClosed :: Range a -> Bool Source
class (PGType tr, PGType t) => PGRangeType tr t | tr -> t where Source
Class indicating that the first PostgreSQL type is a range of the second.
This implies PGParameter
and PGColumn
instances that will work for any type.
Minimal complete definition
Nothing
Methods
pgRangeElementType :: PGTypeName tr -> PGTypeName t Source
Instances
PGRangeType "daterange" "date" | |
PGRangeType "int4range" "integer" | |
PGRangeType "int8range" "bigint" | |
PGRangeType "numrange" "numeric" | |
PGRangeType "tsrange" "timestamp without time zone" | |
PGRangeType "tstzrange" "timestamp with time zone" |