Copyright | (c) Eitan Chatav 2019 |
---|---|
Maintainer | [email protected] |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Squeal.PostgreSQL.Expression
Description
Expressions are the atoms used to build statements.
Synopsis
- newtype Expression (grp :: Grouping) (lat :: FromType) (with :: FromType) (db :: SchemasType) (params :: [NullType]) (from :: FromType) (ty :: NullType) = UnsafeExpression {}
- type Expr x = forall grp lat with db params from. Expression grp lat with db params from x
- type (-->) x y = forall db. Fun db x y
- type Fun db x y = forall grp lat with params from. Expression grp lat with db params from x -> Expression grp lat with db params from y
- unsafeFunction :: ByteString -> x --> y
- function :: (Has sch db schema, Has fun schema (Function ('[x] :=> Returns y))) => QualifiedAlias sch fun -> Fun db x y
- unsafeLeftOp :: ByteString -> x --> y
- unsafeRightOp :: ByteString -> x --> y
- type Operator x1 x2 y = forall grp lat with db params from. Expression grp lat with db params from x1 -> Expression grp lat with db params from x2 -> Expression grp lat with db params from y
- type OperatorDB db x1 x2 y = forall grp lat with params from. Expression grp lat with db params from x1 -> Expression grp lat with db params from x2 -> Expression grp lat with db params from y
- unsafeBinaryOp :: ByteString -> Operator ty0 ty1 ty2
- class PGSubset ty where
- class PGIntersect ty where
- type FunctionVar x0 x1 y = forall grp lat with db params from. [Expression grp lat with db params from x0] -> Expression grp lat with db params from x1 -> Expression grp lat with db params from y
- unsafeFunctionVar :: ByteString -> FunctionVar x0 x1 y
- type (--->) xs y = forall db. FunN db xs y
- type FunN db xs y = forall grp lat with params from. NP (Expression grp lat with db params from) xs -> Expression grp lat with db params from y
- unsafeFunctionN :: SListI xs => ByteString -> xs ---> y
- functionN :: (Has sch db schema, Has fun schema (Function (xs :=> Returns y)), SListI xs) => QualifiedAlias sch fun -> FunN db xs y
- (&) :: a -> (a -> b) -> b
Expression
newtype Expression (grp :: Grouping) (lat :: FromType) (with :: FromType) (db :: SchemasType) (params :: [NullType]) (from :: FromType) (ty :: NullType) Source #
Expression
s are used in a variety of contexts,
such as in the target List
of the
select
command,
as new column values in insertInto
or
update
,
or in search Condition
s
in a number of commands.
The expression syntax allows the calculation of values from primitive expression using arithmetic, logical, and other operations.
The type parameters of Expression
are
lat ::
FromType
, thefrom
clauses of any lat queries in which theExpression
is a correlated subquery expression;with ::
FromType
, theCommonTableExpression
s that are in scope for theExpression
;grp ::
Grouping
, theGrouping
of thefrom
clause which may limit which columns may be referenced by alias;db ::
SchemasType
, the schemas of your database that are in scope for theExpression
;from ::
FromType
, thefrom
clause which theExpression
may use to reference columns by alias;ty ::
NullType
, the type of theExpression
.
Constructors
UnsafeExpression | |
Fields |
Instances
Aggregate AggregateArg (Expression (Grouped bys) :: FromType -> FromType -> SchemasType -> [NullType] -> FromType -> NullType -> Type) Source # | |
Defined in Squeal.PostgreSQL.Expression.Aggregate Methods countStar :: Expression (Grouped bys) lat with db params from (NotNull PGint8) Source # count :: AggregateArg (ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (NotNull PGint8) Source # sum_ :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null (PGSum ty)) Source # arrayAgg :: AggregateArg (ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null (PGvararray ty)) Source # jsonAgg :: AggregateArg (ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGjson) Source # jsonbAgg :: AggregateArg (ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGjsonb) Source # bitAnd :: In int PGIntegral => AggregateArg (null int ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null int) Source # bitOr :: In int PGIntegral => AggregateArg (null int ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null int) Source # boolAnd :: AggregateArg (null PGbool ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGbool) Source # boolOr :: AggregateArg (null PGbool ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGbool) Source # every :: AggregateArg (null PGbool ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGbool) Source # max_ :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null ty) Source # min_ :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null ty) Source # avg :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null (PGAvg ty)) Source # corr :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # covarPop :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # covarSamp :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # regrAvgX :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # regrAvgY :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # regrCount :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGint8) Source # regrIntercept :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # regrR2 :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # regrSlope :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # regrSxx :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # regrSxy :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # regrSyy :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # stddev :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null (PGAvg ty)) Source # stddevPop :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null (PGAvg ty)) Source # stddevSamp :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null (PGAvg ty)) Source # variance :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null (PGAvg ty)) Source # varPop :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null (PGAvg ty)) Source # varSamp :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null (PGAvg ty)) Source # | |
(Has tab (Join lat from) row, Has col row ty, GroupedBy tab col bys, columns ~ ((col ::: ty) ': ([] :: [(Symbol, NullType)]))) => IsQualified tab col (NP (Aliased (Expression (Grouped bys) lat with db params from)) columns) Source # | |
Defined in Squeal.PostgreSQL.Expression | |
(Has tab (Join lat from) row, Has col row ty, GroupedBy tab col bys, column ~ (col ::: ty)) => IsQualified tab col (Aliased (Expression (Grouped bys) lat with db params from) column) Source # | |
Defined in Squeal.PostgreSQL.Expression | |
(Has tab (Join lat from) row, Has col row ty, GroupedBy tab col bys, tys ~ (ty ': ([] :: [NullType]))) => IsQualified tab col (NP (Expression (Grouped bys) lat with db params from) tys) Source # | |
Defined in Squeal.PostgreSQL.Expression | |
(Has tab (Join lat from) row, Has col row ty, columns ~ ((col ::: ty) ': ([] :: [(Symbol, NullType)]))) => IsQualified tab col (NP (Aliased (Expression Ungrouped lat with db params from)) columns) Source # | |
Defined in Squeal.PostgreSQL.Expression | |
(Has tab (Join lat from) row, Has col row ty, column ~ (col ::: ty)) => IsQualified tab col (Aliased (Expression Ungrouped lat with db params from) column) Source # | |
Defined in Squeal.PostgreSQL.Expression | |
(Has tab (Join lat from) row, Has col row ty, tys ~ (ty ': ([] :: [NullType]))) => IsQualified tab col (NP (Expression Ungrouped lat with db params from) tys) Source # | |
Defined in Squeal.PostgreSQL.Expression | |
(Has tab (Join lat from) row, Has col row ty, GroupedBy tab col bys) => IsQualified tab col (Expression (Grouped bys) lat with db params from ty) Source # | |
Defined in Squeal.PostgreSQL.Expression | |
(Has tab (Join lat from) row, Has col row ty) => IsQualified tab col (Expression Ungrouped lat with db params from ty) Source # | |
Defined in Squeal.PostgreSQL.Expression | |
(HasUnique tab (Join lat from) row, Has col row ty, GroupedBy tab col bys, columns ~ ((col ::: ty) ': ([] :: [(Symbol, NullType)]))) => IsLabel col (NP (Aliased (Expression (Grouped bys) lat with db params from)) columns) Source # | |
Defined in Squeal.PostgreSQL.Expression | |
(HasUnique tab (Join lat from) row, Has col row ty, GroupedBy tab col bys, column ~ (col ::: ty)) => IsLabel col (Aliased (Expression (Grouped bys) lat with db params from) column) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods fromLabel :: Aliased (Expression (Grouped bys) lat with db params from) column # | |
(HasUnique tab (Join lat from) row, Has col row ty, GroupedBy tab col bys, tys ~ (ty ': ([] :: [NullType]))) => IsLabel col (NP (Expression (Grouped bys) lat with db params from) tys) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods fromLabel :: NP (Expression (Grouped bys) lat with db params from) tys # | |
(HasUnique tab (Join lat from) row, Has col row ty, columns ~ ((col ::: ty) ': ([] :: [(Symbol, NullType)]))) => IsLabel col (NP (Aliased (Expression Ungrouped lat with db params from)) columns) Source # | |
Defined in Squeal.PostgreSQL.Expression | |
(HasUnique tab (Join lat from) row, Has col row ty, column ~ (col ::: ty)) => IsLabel col (Aliased (Expression Ungrouped lat with db params from) column) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods fromLabel :: Aliased (Expression Ungrouped lat with db params from) column # | |
(HasUnique tab (Join lat from) row, Has col row ty, tys ~ (ty ': ([] :: [NullType]))) => IsLabel col (NP (Expression Ungrouped lat with db params from) tys) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods fromLabel :: NP (Expression Ungrouped lat with db params from) tys # | |
(HasUnique tab (Join lat from) row, Has col row ty, GroupedBy tab col bys) => IsLabel col (Expression (Grouped bys) lat with db params from ty) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods fromLabel :: Expression (Grouped bys) lat with db params from ty # | |
(HasUnique tab (Join lat from) row, Has col row ty) => IsLabel col (Expression Ungrouped lat with db params from ty) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods fromLabel :: Expression Ungrouped lat with db params from ty # | |
(KnownSymbol label, In label labels) => IsPGlabel label (Expression grp lat with db params from (null (PGenum labels))) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods label :: Expression grp lat with db params from (null (PGenum labels)) Source # | |
(KnownSymbol col, row ~ ((col ::: ty) ': ([] :: [(Symbol, NullType)]))) => Aliasable col (Expression grp lat with db params from ty) (Selection grp lat with db params from row) Source # | |
Defined in Squeal.PostgreSQL.Query.Select | |
Eq (Expression grp lat with db params from ty) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods (==) :: Expression grp lat with db params from ty -> Expression grp lat with db params from ty -> Bool # (/=) :: Expression grp lat with db params from ty -> Expression grp lat with db params from ty -> Bool # | |
Floating (Expression grp lat with db params from (null PGnumeric)) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods pi :: Expression grp lat with db params from (null PGnumeric) # exp :: Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) # log :: Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) # sqrt :: Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) # (**) :: Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) # logBase :: Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) # sin :: Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) # cos :: Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) # tan :: Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) # asin :: Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) # acos :: Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) # atan :: Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) # sinh :: Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) # cosh :: Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) # tanh :: Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) # asinh :: Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) # acosh :: Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) # atanh :: Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) # log1p :: Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) # expm1 :: Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) # log1pexp :: Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) # log1mexp :: Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) # | |
Floating (Expression grp lat with db params from (null PGfloat8)) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods pi :: Expression grp lat with db params from (null PGfloat8) # exp :: Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) # log :: Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) # sqrt :: Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) # (**) :: Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) # logBase :: Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) # sin :: Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) # cos :: Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) # tan :: Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) # asin :: Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) # acos :: Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) # atan :: Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) # sinh :: Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) # cosh :: Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) # tanh :: Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) # asinh :: Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) # acosh :: Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) # atanh :: Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) # log1p :: Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) # expm1 :: Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) # log1pexp :: Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) # log1mexp :: Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) # | |
Floating (Expression grp lat with db params from (null PGfloat4)) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods pi :: Expression grp lat with db params from (null PGfloat4) # exp :: Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) # log :: Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) # sqrt :: Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) # (**) :: Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) # logBase :: Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) # sin :: Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) # cos :: Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) # tan :: Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) # asin :: Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) # acos :: Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) # atan :: Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) # sinh :: Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) # cosh :: Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) # tanh :: Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) # asinh :: Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) # acosh :: Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) # atanh :: Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) # log1p :: Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) # expm1 :: Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) # log1pexp :: Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) # log1mexp :: Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) # | |
Fractional (Expression grp lat with db params from (null PGnumeric)) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods (/) :: Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) # recip :: Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) # fromRational :: Rational -> Expression grp lat with db params from (null PGnumeric) # | |
Fractional (Expression grp lat with db params from (null PGfloat8)) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods (/) :: Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) # recip :: Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) # fromRational :: Rational -> Expression grp lat with db params from (null PGfloat8) # | |
Fractional (Expression grp lat with db params from (null PGfloat4)) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods (/) :: Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) # recip :: Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) # fromRational :: Rational -> Expression grp lat with db params from (null PGfloat4) # | |
Num (Expression grp lat with db params from (null PGnumeric)) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods (+) :: Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) # (-) :: Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) # (*) :: Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) # negate :: Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) # abs :: Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) # signum :: Expression grp lat with db params from (null PGnumeric) -> Expression grp lat with db params from (null PGnumeric) # fromInteger :: Integer -> Expression grp lat with db params from (null PGnumeric) # | |
Num (Expression grp lat with db params from (null PGfloat8)) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods (+) :: Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) # (-) :: Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) # (*) :: Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) # negate :: Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) # abs :: Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) # signum :: Expression grp lat with db params from (null PGfloat8) -> Expression grp lat with db params from (null PGfloat8) # fromInteger :: Integer -> Expression grp lat with db params from (null PGfloat8) # | |
Num (Expression grp lat with db params from (null PGfloat4)) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods (+) :: Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) # (-) :: Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) # (*) :: Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) # negate :: Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) # abs :: Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) # signum :: Expression grp lat with db params from (null PGfloat4) -> Expression grp lat with db params from (null PGfloat4) # fromInteger :: Integer -> Expression grp lat with db params from (null PGfloat4) # | |
Num (Expression grp lat with db params from (null PGint8)) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods (+) :: Expression grp lat with db params from (null PGint8) -> Expression grp lat with db params from (null PGint8) -> Expression grp lat with db params from (null PGint8) # (-) :: Expression grp lat with db params from (null PGint8) -> Expression grp lat with db params from (null PGint8) -> Expression grp lat with db params from (null PGint8) # (*) :: Expression grp lat with db params from (null PGint8) -> Expression grp lat with db params from (null PGint8) -> Expression grp lat with db params from (null PGint8) # negate :: Expression grp lat with db params from (null PGint8) -> Expression grp lat with db params from (null PGint8) # abs :: Expression grp lat with db params from (null PGint8) -> Expression grp lat with db params from (null PGint8) # signum :: Expression grp lat with db params from (null PGint8) -> Expression grp lat with db params from (null PGint8) # fromInteger :: Integer -> Expression grp lat with db params from (null PGint8) # | |
Num (Expression grp lat with db params from (null PGint4)) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods (+) :: Expression grp lat with db params from (null PGint4) -> Expression grp lat with db params from (null PGint4) -> Expression grp lat with db params from (null PGint4) # (-) :: Expression grp lat with db params from (null PGint4) -> Expression grp lat with db params from (null PGint4) -> Expression grp lat with db params from (null PGint4) # (*) :: Expression grp lat with db params from (null PGint4) -> Expression grp lat with db params from (null PGint4) -> Expression grp lat with db params from (null PGint4) # negate :: Expression grp lat with db params from (null PGint4) -> Expression grp lat with db params from (null PGint4) # abs :: Expression grp lat with db params from (null PGint4) -> Expression grp lat with db params from (null PGint4) # signum :: Expression grp lat with db params from (null PGint4) -> Expression grp lat with db params from (null PGint4) # fromInteger :: Integer -> Expression grp lat with db params from (null PGint4) # | |
Num (Expression grp lat with db params from (null PGint2)) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods (+) :: Expression grp lat with db params from (null PGint2) -> Expression grp lat with db params from (null PGint2) -> Expression grp lat with db params from (null PGint2) # (-) :: Expression grp lat with db params from (null PGint2) -> Expression grp lat with db params from (null PGint2) -> Expression grp lat with db params from (null PGint2) # (*) :: Expression grp lat with db params from (null PGint2) -> Expression grp lat with db params from (null PGint2) -> Expression grp lat with db params from (null PGint2) # negate :: Expression grp lat with db params from (null PGint2) -> Expression grp lat with db params from (null PGint2) # abs :: Expression grp lat with db params from (null PGint2) -> Expression grp lat with db params from (null PGint2) # signum :: Expression grp lat with db params from (null PGint2) -> Expression grp lat with db params from (null PGint2) # fromInteger :: Integer -> Expression grp lat with db params from (null PGint2) # | |
Ord (Expression grp lat with db params from ty) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods compare :: Expression grp lat with db params from ty -> Expression grp lat with db params from ty -> Ordering # (<) :: Expression grp lat with db params from ty -> Expression grp lat with db params from ty -> Bool # (<=) :: Expression grp lat with db params from ty -> Expression grp lat with db params from ty -> Bool # (>) :: Expression grp lat with db params from ty -> Expression grp lat with db params from ty -> Bool # (>=) :: Expression grp lat with db params from ty -> Expression grp lat with db params from ty -> Bool # max :: Expression grp lat with db params from ty -> Expression grp lat with db params from ty -> Expression grp lat with db params from ty # min :: Expression grp lat with db params from ty -> Expression grp lat with db params from ty -> Expression grp lat with db params from ty # | |
Show (Expression grp lat with db params from ty) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods showsPrec :: Int -> Expression grp lat with db params from ty -> ShowS # show :: Expression grp lat with db params from ty -> String # showList :: [Expression grp lat with db params from ty] -> ShowS # | |
IsString (Expression grp lat with db params from (null PGtsquery)) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods fromString :: String -> Expression grp lat with db params from (null PGtsquery) # | |
IsString (Expression grp lat with db params from (null PGtsvector)) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods fromString :: String -> Expression grp lat with db params from (null PGtsvector) # | |
IsString (Expression grp lat with db params from (null PGtext)) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods fromString :: String -> Expression grp lat with db params from (null PGtext) # | |
Generic (Expression grp lat with db params from ty) Source # | |
Defined in Squeal.PostgreSQL.Expression Associated Types type Rep (Expression grp lat with db params from ty) :: Type -> Type # Methods from :: Expression grp lat with db params from ty -> Rep (Expression grp lat with db params from ty) x # to :: Rep (Expression grp lat with db params from ty) x -> Expression grp lat with db params from ty # | |
Semigroup (Expression grp lat with db params from (null PGtsvector)) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods (<>) :: Expression grp lat with db params from (null PGtsvector) -> Expression grp lat with db params from (null PGtsvector) -> Expression grp lat with db params from (null PGtsvector) # sconcat :: NonEmpty (Expression grp lat with db params from (null PGtsvector)) -> Expression grp lat with db params from (null PGtsvector) # stimes :: Integral b => b -> Expression grp lat with db params from (null PGtsvector) -> Expression grp lat with db params from (null PGtsvector) # | |
Semigroup (Expression grp lat with db params from (null PGtext)) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods (<>) :: Expression grp lat with db params from (null PGtext) -> Expression grp lat with db params from (null PGtext) -> Expression grp lat with db params from (null PGtext) # sconcat :: NonEmpty (Expression grp lat with db params from (null PGtext)) -> Expression grp lat with db params from (null PGtext) # stimes :: Integral b => b -> Expression grp lat with db params from (null PGtext) -> Expression grp lat with db params from (null PGtext) # | |
Semigroup (Expression grp lat with db params from (null PGjsonb)) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods (<>) :: Expression grp lat with db params from (null PGjsonb) -> Expression grp lat with db params from (null PGjsonb) -> Expression grp lat with db params from (null PGjsonb) # sconcat :: NonEmpty (Expression grp lat with db params from (null PGjsonb)) -> Expression grp lat with db params from (null PGjsonb) # stimes :: Integral b => b -> Expression grp lat with db params from (null PGjsonb) -> Expression grp lat with db params from (null PGjsonb) # | |
Semigroup (Expression grp lat with db params from (null (PGvararray ty))) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods (<>) :: Expression grp lat with db params from (null (PGvararray ty)) -> Expression grp lat with db params from (null (PGvararray ty)) -> Expression grp lat with db params from (null (PGvararray ty)) # sconcat :: NonEmpty (Expression grp lat with db params from (null (PGvararray ty))) -> Expression grp lat with db params from (null (PGvararray ty)) # stimes :: Integral b => b -> Expression grp lat with db params from (null (PGvararray ty)) -> Expression grp lat with db params from (null (PGvararray ty)) # | |
Monoid (Expression grp lat with db params from (null PGtsvector)) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods mempty :: Expression grp lat with db params from (null PGtsvector) # mappend :: Expression grp lat with db params from (null PGtsvector) -> Expression grp lat with db params from (null PGtsvector) -> Expression grp lat with db params from (null PGtsvector) # mconcat :: [Expression grp lat with db params from (null PGtsvector)] -> Expression grp lat with db params from (null PGtsvector) # | |
Monoid (Expression grp lat with db params from (null PGtext)) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods mempty :: Expression grp lat with db params from (null PGtext) # mappend :: Expression grp lat with db params from (null PGtext) -> Expression grp lat with db params from (null PGtext) -> Expression grp lat with db params from (null PGtext) # mconcat :: [Expression grp lat with db params from (null PGtext)] -> Expression grp lat with db params from (null PGtext) # | |
NFData (Expression grp lat with db params from ty) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods rnf :: Expression grp lat with db params from ty -> () # | |
RenderSQL (Expression grp lat with db params from ty) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods renderSQL :: Expression grp lat with db params from ty -> ByteString Source # | |
type Rep (Expression grp lat with db params from ty) Source # | |
Defined in Squeal.PostgreSQL.Expression type Rep (Expression grp lat with db params from ty) = D1 (MetaData "Expression" "Squeal.PostgreSQL.Expression" "squeal-postgresql-0.6.0.2-55PJjSRSXxzaZJfRqaJ60" True) (C1 (MetaCons "UnsafeExpression" PrefixI True) (S1 (MetaSel (Just "renderExpression") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString))) |
Arguments
= Expression grp lat with db params from x | cannot reference aliases |
An Expr
is a closed Expression
.
It is a FRankNType
but don't be scared.
Think of it as an expression which sees no
namespaces, so you can't use parameters
or alias references. It can be used as
a simple piece of more complex Expression
s.
Function
Arguments
= Expression grp lat with db params from x | input |
-> Expression grp lat with db params from y | output |
Like -->
but depends on the schemas of the database
unsafeFunction :: ByteString -> x --> y Source #
>>>
printSQL $ unsafeFunction "f" true
f(TRUE)
Arguments
:: (Has sch db schema, Has fun schema (Function ('[x] :=> Returns y))) | |
=> QualifiedAlias sch fun | function name |
-> Fun db x y |
Call a user defined function of a single variable
>>>
type Fn = '[ 'Null 'PGint4] :=> 'Returns ('NotNull 'PGnumeric)
>>>
type Schema = '["fn" ::: 'Function Fn]
>>>
:{
let fn :: Fun (Public Schema) ('Null 'PGint4) ('NotNull 'PGnumeric) fn = function #fn in printSQL (fn 1) :} "fn"((1 :: int4))
unsafeLeftOp :: ByteString -> x --> y Source #
>>>
printSQL $ unsafeLeftOp "NOT" true
(NOT TRUE)
unsafeRightOp :: ByteString -> x --> y Source #
>>>
printSQL $ true & unsafeRightOp "IS NOT TRUE"
(TRUE IS NOT TRUE)
Operator
type Operator x1 x2 y Source #
Arguments
= Expression grp lat with db params from x1 | left input |
-> Expression grp lat with db params from x2 | right input |
-> Expression grp lat with db params from y | output |
A RankNType
for binary operators.
type OperatorDB db x1 x2 y Source #
Arguments
= Expression grp lat with db params from x1 | left input |
-> Expression grp lat with db params from x2 | right input |
-> Expression grp lat with db params from y | output |
Like Operator
but depends on the schemas of the database
unsafeBinaryOp :: ByteString -> Operator ty0 ty1 ty2 Source #
>>>
printSQL $ unsafeBinaryOp "OR" true false
(TRUE OR FALSE)
class PGSubset ty where Source #
Contained by operators
Minimal complete definition
Nothing
Methods
(@>) :: Operator (null0 ty) (null1 ty) (Null PGbool) Source #
(<@) :: Operator (null0 ty) (null1 ty) (Null PGbool) Source #
Instances
PGSubset PGjsonb Source # | |
PGSubset PGtsquery Source # | |
PGSubset (PGvararray ty :: PGType) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods (@>) :: Operator (null0 (PGvararray ty)) (null1 (PGvararray ty)) (Null PGbool) Source # (<@) :: Operator (null0 (PGvararray ty)) (null1 (PGvararray ty)) (Null PGbool) Source # | |
PGSubset (PGrange ty :: PGType) Source # | |
class PGIntersect ty where Source #
Intersection operator
Minimal complete definition
Nothing
Instances
PGIntersect (PGvararray ty :: PGType) Source # | |
Defined in Squeal.PostgreSQL.Expression Methods (@&&) :: Operator (null0 (PGvararray ty)) (null1 (PGvararray ty)) (Null PGbool) Source # | |
PGIntersect (PGrange ty :: PGType) Source # | |
Multivariable Function
type FunctionVar x0 x1 y Source #
Arguments
= [Expression grp lat with db params from x0] | inputs |
-> Expression grp lat with db params from x1 | must have at least 1 input |
-> Expression grp lat with db params from y | output |
A RankNType
for functions with a variable-length list of
homogeneous arguments and at least 1 more argument.
unsafeFunctionVar :: ByteString -> FunctionVar x0 x1 y Source #
>>>
printSQL (unsafeFunctionVar "greatest" [true, null_] false)
greatest(TRUE, NULL, FALSE)
type (--->) xs y = forall db. FunN db xs y Source #
A RankNType
for functions with a fixed-length list of heterogeneous arguments.
Use the *:
operator to end your argument lists, like so.
>>>
printSQL (unsafeFunctionN "fun" (true :* false :* localTime *: true))
fun(TRUE, FALSE, LOCALTIME, TRUE)
Arguments
= NP (Expression grp lat with db params from) xs | inputs |
-> Expression grp lat with db params from y | output |
Like --->
but depends on the schemas of the database
unsafeFunctionN :: SListI xs => ByteString -> xs ---> y Source #
>>>
printSQL $ unsafeFunctionN "f" (currentTime :* localTimestamp :* false *: inline 'a')
f(CURRENT_TIME, LOCALTIMESTAMP, FALSE, (E'a' :: char(1)))
Arguments
:: (Has sch db schema, Has fun schema (Function (xs :=> Returns y)), SListI xs) | |
=> QualifiedAlias sch fun | function alias |
-> FunN db xs y |
Call a user defined multivariable function
>>>
type Fn = '[ 'Null 'PGint4, 'Null 'PGbool] :=> 'Returns ('NotNull 'PGnumeric)
>>>
type Schema = '["fn" ::: 'Function Fn]
>>>
:{
let fn :: FunN (Public Schema) '[ 'Null 'PGint4, 'Null 'PGbool] ('NotNull 'PGnumeric) fn = functionN #fn in printSQL (fn (1 *: true)) :} "fn"((1 :: int4), TRUE)