squeal-postgresql-0.7.0.1: Squeal PostgreSQL Library

Copyright(c) Eitan Chatav 2019
Maintainereitan@morphism.tech
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Squeal.PostgreSQL.Expression.Time

Contents

Description

date/time functions and operators

Synopsis

Time Operation

class TimeOp time diff | time -> diff where Source #

Affine space operations on time types.

Minimal complete definition

Nothing

Methods

(!+) :: Operator (null time) (null diff) (null time) infixl 6 Source #

>>> printSQL (makeDate (1984 :* 7 *: 3) !+ 365)
(make_date((1984 :: int4), (7 :: int4), (3 :: int4)) + (365 :: int4))

(+!) :: Operator (null diff) (null time) (null time) infixl 6 Source #

>>> printSQL (365 +! makeDate (1984 :* 7 *: 3))
((365 :: int4) + make_date((1984 :: int4), (7 :: int4), (3 :: int4)))

(!-) :: Operator (null time) (null diff) (null time) infixl 6 Source #

>>> printSQL (makeDate (1984 :* 7 *: 3) !- 365)
(make_date((1984 :: int4), (7 :: int4), (3 :: int4)) - (365 :: int4))

(!-!) :: Operator (null time) (null time) (null diff) infixl 6 Source #

>>> printSQL (makeDate (1984 :* 7 *: 3) !-! currentDate)
(make_date((1984 :: int4), (7 :: int4), (3 :: int4)) - CURRENT_DATE)
Instances
TimeOp PGtimestamp PGinterval Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Time

TimeOp PGtimestamptz PGinterval Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Time

TimeOp PGdate PGint4 Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Time

Methods

(!+) :: Operator (null PGdate) (null PGint4) (null PGdate) Source #

(+!) :: Operator (null PGint4) (null PGdate) (null PGdate) Source #

(!-) :: Operator (null PGdate) (null PGint4) (null PGdate) Source #

(!-!) :: Operator (null PGdate) (null PGdate) (null PGint4) Source #

TimeOp PGtime PGinterval Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Time

Methods

(!+) :: Operator (null PGtime) (null PGinterval) (null PGtime) Source #

(+!) :: Operator (null PGinterval) (null PGtime) (null PGtime) Source #

(!-) :: Operator (null PGtime) (null PGinterval) (null PGtime) Source #

(!-!) :: Operator (null PGtime) (null PGtime) (null PGinterval) Source #

TimeOp PGtimetz PGinterval Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Time

Methods

(!+) :: Operator (null PGtimetz) (null PGinterval) (null PGtimetz) Source #

(+!) :: Operator (null PGinterval) (null PGtimetz) (null PGtimetz) Source #

(!-) :: Operator (null PGtimetz) (null PGinterval) (null PGtimetz) Source #

(!-!) :: Operator (null PGtimetz) (null PGtimetz) (null PGinterval) Source #

TimeOp PGinterval PGinterval Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Time

Time Function

currentDate :: Expr (null PGdate) Source #

>>> printSQL currentDate
CURRENT_DATE

currentTime :: Expr (null PGtimetz) Source #

>>> printSQL currentTime
CURRENT_TIME

currentTimestamp :: Expr (null PGtimestamptz) Source #

>>> printSQL currentTimestamp
CURRENT_TIMESTAMP

localTime :: Expr (null PGtime) Source #

>>> printSQL localTime
LOCALTIME

localTimestamp :: Expr (null PGtimestamp) Source #

>>> printSQL localTimestamp
LOCALTIMESTAMP

now :: Expr (null PGtimestamptz) Source #

Current date and time (equivalent to currentTimestamp)

>>> printSQL now
now()

makeDate :: '[null PGint4, null PGint4, null PGint4] ---> null PGdate Source #

Create date from year, month and day fields

>>> printSQL (makeDate (1984 :* 7 *: 3))
make_date((1984 :: int4), (7 :: int4), (3 :: int4))

makeTime :: '[null PGint4, null PGint4, null PGfloat8] ---> null PGtime Source #

Create time from hour, minute and seconds fields

>>> printSQL (makeTime (8 :* 15 *: 23.5))
make_time((8 :: int4), (15 :: int4), (23.5 :: float8))

makeTimestamp :: '[null PGint4, null PGint4, null PGint4, null PGint4, null PGint4, null PGfloat8] ---> null PGtimestamp Source #

Create timestamp from year, month, day, hour, minute and seconds fields

>>> printSQL (makeTimestamp (2013 :* 7 :* 15 :* 8 :* 15 *: 23.5))
make_timestamp((2013 :: int4), (7 :: int4), (15 :: int4), (8 :: int4), (15 :: int4), (23.5 :: float8))

makeTimestamptz :: '[null PGint4, null PGint4, null PGint4, null PGint4, null PGint4, null PGfloat8] ---> null PGtimestamptz Source #

Create timestamp with time zone from year, month, day, hour, minute and seconds fields; the current time zone is used

>>> printSQL (makeTimestamptz (2013 :* 7 :* 15 :* 8 :* 15 *: 23.5))
make_timestamptz((2013 :: int4), (7 :: int4), (15 :: int4), (8 :: int4), (15 :: int4), (23.5 :: float8))

Interval

interval_ :: Milli -> TimeUnit -> Expr (null PGinterval) Source #

>>> printSQL $ interval_ 7 Days
(INTERVAL '7.000 days')

data TimeUnit Source #

A TimeUnit to use in interval_ construction.

Instances
Enum TimeUnit Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Time

Eq TimeUnit Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Time

Ord TimeUnit Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Time

Read TimeUnit Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Time

Show TimeUnit Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Time

Generic TimeUnit Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Time

Associated Types

type Rep TimeUnit :: Type -> Type #

Methods

from :: TimeUnit -> Rep TimeUnit x #

to :: Rep TimeUnit x -> TimeUnit #

Generic TimeUnit Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Time

Associated Types

type Code TimeUnit :: [[Type]] #

HasDatatypeInfo TimeUnit Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Time

Associated Types

type DatatypeInfoOf TimeUnit :: DatatypeInfo #

RenderSQL TimeUnit Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Time

type Rep TimeUnit Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Time

type Rep TimeUnit = D1 (MetaData "TimeUnit" "Squeal.PostgreSQL.Expression.Time" "squeal-postgresql-0.7.0.1-33cXMmdyUeW5J6FQU4gmil" False) (((C1 (MetaCons "Years" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Months" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Weeks" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "Days" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Hours" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Minutes" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "Seconds" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Microseconds" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Milliseconds" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "Decades" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Centuries" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Millennia" PrefixI False) (U1 :: Type -> Type)))))
type Code TimeUnit Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Time

type DatatypeInfoOf TimeUnit Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Time