postgresql-typed-0.4.1: A PostgreSQL access library with compile-time SQL type inference

Copyright2015 Dylan Simon
Safe HaskellNone
LanguageHaskell98

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.

Synopsis

Documentation

data Bound a Source

A end-point for a range, which may be nothing (infinity, NULL in PostgreSQL), open (inclusive), or closed (exclusive)

Constructors

Unbounded

Equivalent to Bounded False ±Infinity

Bounded 

Fields

_boundClosed :: Bool

True if the range includes this bound

_bound :: a
 

Instances

Functor Bound 
Eq a => Eq (Bound a) 

newtype LowerBound a Source

Constructors

Lower 

Fields

boundLower :: Bound a
 

Instances

Functor LowerBound 
Bounded a => Bounded (LowerBound a)

The constraint is only necessary for maxBound, unfortunately

Eq a => Eq (LowerBound a) 
Ord a => Ord (LowerBound a)

Takes into account open vs. closed (but does not understand equivalent discrete bounds)

newtype UpperBound a Source

Constructors

Upper 

Fields

boundUpper :: Bound a
 

Instances

Functor UpperBound 
Bounded a => Bounded (UpperBound a)

The constraint is only necessary for minBound, unfortunately

Eq a => Eq (UpperBound a) 
Ord a => Ord (UpperBound a)

Takes into account open vs. closed (but does not understand equivalent discrete bounds)

data Range a Source

Constructors

Empty 
Range 

Fields

lower :: LowerBound a
 
upper :: 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) 
Ord a => Monoid (Range a) 

boundClosed :: Bound a -> Bool Source

Unbounded endpoints are always open.

makeBound :: Bool -> Maybe a -> Bound a Source

Construct from parts: makeBound (boundClosed b) (bound b) == b

lowerBound :: Range a -> Bound a Source

Empty ranges treated as Unbounded

upperBound :: Range a -> Bound a Source

Empty ranges treated as Unbounded

lowerClosed :: Range a -> Bool Source

Equivalent to boundClosed . lowerBound

upperClosed :: Range a -> Bool Source

Equivalent to boundClosed . upperBound

isEmpty :: Ord a => Range a -> Bool Source

point :: Eq a => a -> Range a Source

Create a point range [x,x]

getPoint :: Eq a => Range a -> Maybe a Source

Extract a point: getPoint (point x) == Just x

range :: Ord a => Bound a -> Bound a -> Range a Source

normal :: Ord a => Maybe a -> Maybe a -> Range a Source

bounded :: Ord a => a -> a -> Range a Source

normalize :: Ord a => Range a -> Range a Source

normalize' :: (Ord a, Enum a) => Range a -> Range a Source

normalize for discrete (non-continuous) range types, using the Enum instance

(@>) :: Ord a => Range a -> Range a -> Bool Source

Contains range

(<@) :: Ord a => Range a -> Range a -> Bool Source

Contains range

(@>.) :: Ord a => Range a -> a -> Bool Source

Contains element

overlaps :: Ord a => Range a -> Range a -> Bool Source

intersect :: Ord a => Range a -> Range a -> Range a 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

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"