postgresql-typed-0.6.2.0: PostgreSQL interface with compile-time SQL type checking, optional HDBC backend
Copyright2015 Dylan Simon
Safe HaskellNone
LanguageHaskell2010

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

Instances

Instances details
Functor Bound Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Range

Methods

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

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

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

Defined in Database.PostgreSQL.Typed.Range

Methods

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

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

newtype LowerBound a Source #

Constructors

Lower 

Fields

Instances

Instances details
Functor LowerBound Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Range

Methods

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

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

Bounded a => Bounded (LowerBound a) Source #

The constraint is only necessary for maxBound, unfortunately

Instance details

Defined in Database.PostgreSQL.Typed.Range

Eq a => Eq (LowerBound a) Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Range

Methods

(==) :: LowerBound a -> LowerBound a -> Bool #

(/=) :: LowerBound a -> LowerBound a -> Bool #

Ord a => Ord (LowerBound a) Source #

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

Instance details

Defined in Database.PostgreSQL.Typed.Range

newtype UpperBound a Source #

Constructors

Upper 

Fields

Instances

Instances details
Functor UpperBound Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Range

Methods

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

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

Bounded a => Bounded (UpperBound a) Source #

The constraint is only necessary for minBound, unfortunately

Instance details

Defined in Database.PostgreSQL.Typed.Range

Eq a => Eq (UpperBound a) Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Range

Methods

(==) :: UpperBound a -> UpperBound a -> Bool #

(/=) :: UpperBound a -> UpperBound a -> Bool #

Ord a => Ord (UpperBound a) Source #

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

Instance details

Defined in Database.PostgreSQL.Typed.Range

data Range a Source #

Constructors

Empty 
Range 

Fields

Instances

Instances details
Functor Range Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Range

Methods

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

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

(PGRangeType t, PGColumn (PGSubType t) a) => PGColumn t (Range a) Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Range

Methods

pgDecode :: PGTypeID t -> PGTextValue -> Range a Source #

pgDecodeBinary :: PGTypeEnv -> PGTypeID t -> PGBinaryValue -> Range a Source #

pgDecodeValue :: PGTypeEnv -> PGTypeID t -> PGValue -> Range a Source #

(PGRangeType t, PGParameter (PGSubType t) a) => PGParameter t (Range a) Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Range

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

Defined in Database.PostgreSQL.Typed.Range

Methods

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

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

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

Defined in Database.PostgreSQL.Typed.Range

Methods

compare :: Range a -> Range a -> Ordering #

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

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

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

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

max :: Range a -> Range a -> Range a #

min :: Range a -> Range a -> Range a #

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

Defined in Database.PostgreSQL.Typed.Range

Methods

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

show :: Range a -> String #

showList :: [Range a] -> ShowS #

Ord a => Semigroup (Range a) Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Range

Methods

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

sconcat :: NonEmpty (Range a) -> Range a #

stimes :: Integral b => b -> Range a -> Range a #

Ord a => Monoid (Range a) Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Range

Methods

mempty :: Range a #

mappend :: Range a -> Range a -> Range a #

mconcat :: [Range a] -> 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 :: 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 #

union :: Ord a => Range a -> Range a -> Range a Source #

Union ranges. Fails if ranges are disjoint.

class (PGType t, PGType (PGSubType t)) => PGRangeType 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

Associated Types

type PGSubType t :: Symbol Source #

Instances

Instances details
PGRangeType "daterange" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Range

Associated Types

type PGSubType "daterange" :: Symbol Source #

Methods

pgRangeElementType :: PGTypeID "daterange" -> PGTypeID (PGSubType "daterange") Source #

PGRangeType "int4range" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Range

Associated Types

type PGSubType "int4range" :: Symbol Source #

Methods

pgRangeElementType :: PGTypeID "int4range" -> PGTypeID (PGSubType "int4range") Source #

PGRangeType "int8range" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Range

Associated Types

type PGSubType "int8range" :: Symbol Source #

Methods

pgRangeElementType :: PGTypeID "int8range" -> PGTypeID (PGSubType "int8range") Source #

PGRangeType "numrange" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Range

Associated Types

type PGSubType "numrange" :: Symbol Source #

Methods

pgRangeElementType :: PGTypeID "numrange" -> PGTypeID (PGSubType "numrange") Source #

PGRangeType "tsrange" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Range

Associated Types

type PGSubType "tsrange" :: Symbol Source #

Methods

pgRangeElementType :: PGTypeID "tsrange" -> PGTypeID (PGSubType "tsrange") Source #

PGRangeType "tstzrange" Source # 
Instance details

Defined in Database.PostgreSQL.Typed.Range

Associated Types

type PGSubType "tstzrange" :: Symbol Source #

Methods

pgRangeElementType :: PGTypeID "tstzrange" -> PGTypeID (PGSubType "tstzrange") Source #

Orphan instances

PGType "daterange" Source # 
Instance details

Associated Types

type PGVal "daterange" Source #

Methods

pgTypeName :: PGTypeID "daterange" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "daterange" -> Bool Source #

PGType "int4range" Source # 
Instance details

Associated Types

type PGVal "int4range" Source #

Methods

pgTypeName :: PGTypeID "int4range" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "int4range" -> Bool Source #

PGType "int8range" Source # 
Instance details

Associated Types

type PGVal "int8range" Source #

Methods

pgTypeName :: PGTypeID "int8range" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "int8range" -> Bool Source #

PGType "numrange" Source # 
Instance details

Associated Types

type PGVal "numrange" Source #

Methods

pgTypeName :: PGTypeID "numrange" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "numrange" -> Bool Source #

PGType "tsrange" Source # 
Instance details

Associated Types

type PGVal "tsrange" Source #

Methods

pgTypeName :: PGTypeID "tsrange" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "tsrange" -> Bool Source #

PGType "tstzrange" Source # 
Instance details

Associated Types

type PGVal "tstzrange" Source #

Methods

pgTypeName :: PGTypeID "tstzrange" -> PGName Source #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "tstzrange" -> Bool Source #