{-# LANGUAGE
DataKinds
, OverloadedStrings
, RankNTypes
, TypeOperators
#-}
module Squeal.PostgreSQL.Expression.Subquery
(
exists
, in_
, notIn
, subAll
, subAny
) where
import Squeal.PostgreSQL.Type.Alias
import Squeal.PostgreSQL.Expression
import Squeal.PostgreSQL.Expression.Logic
import Squeal.PostgreSQL.Type.List
import Squeal.PostgreSQL.Query
import Squeal.PostgreSQL.Render
import Squeal.PostgreSQL.Type.Schema
exists
:: Query (Join lat from) with db params row
-> Expression grp lat with db params from (null 'PGbool)
exists :: Query (Join lat from) with db params row
-> Expression grp lat with db params from (null 'PGbool)
exists Query (Join lat from) with db params row
query = ByteString -> Expression grp lat with db params from (null 'PGbool)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression (ByteString
-> Expression grp lat with db params from (null 'PGbool))
-> ByteString
-> Expression grp lat with db params from (null 'PGbool)
forall a b. (a -> b) -> a -> b
$ ByteString
"EXISTS" ByteString -> ByteString -> ByteString
<+> ByteString -> ByteString
parenthesized (Query (Join lat from) with db params row -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Query (Join lat from) with db params row
query)
subAll
:: Expression grp lat with db params from ty1
-> Operator ty1 ty2 ('Null 'PGbool)
-> Query (Join lat from) with db params '[col ::: ty2]
-> Condition grp lat with db params from
subAll :: Expression grp lat with db params from ty1
-> Operator ty1 ty2 ('Null 'PGbool)
-> Query (Join lat from) with db params '[col ::: ty2]
-> Condition grp lat with db params from
subAll Expression grp lat with db params from ty1
expr Operator ty1 ty2 ('Null 'PGbool)
(?) Query (Join lat from) with db params '[col ::: ty2]
qry = Expression grp lat with db params from ty1
expr Expression grp lat with db params from ty1
-> Expression grp lat with db params from ty2
-> Condition grp lat with db params from
Operator ty1 ty2 ('Null 'PGbool)
?
(ByteString -> Expression grp lat with db params from ty2
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression (ByteString -> Expression grp lat with db params from ty2)
-> ByteString -> Expression grp lat with db params from ty2
forall a b. (a -> b) -> a -> b
$ ByteString
"ALL" ByteString -> ByteString -> ByteString
<+> ByteString -> ByteString
parenthesized (Query (Join lat from) with db params '[col ::: ty2] -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Query (Join lat from) with db params '[col ::: ty2]
qry))
subAny
:: Expression grp lat with db params from ty1
-> Operator ty1 ty2 ('Null 'PGbool)
-> Query (Join lat from) with db params '[col ::: ty2]
-> Condition grp lat with db params from
subAny :: Expression grp lat with db params from ty1
-> Operator ty1 ty2 ('Null 'PGbool)
-> Query (Join lat from) with db params '[col ::: ty2]
-> Condition grp lat with db params from
subAny Expression grp lat with db params from ty1
expr Operator ty1 ty2 ('Null 'PGbool)
(?) Query (Join lat from) with db params '[col ::: ty2]
qry = Expression grp lat with db params from ty1
expr Expression grp lat with db params from ty1
-> Expression grp lat with db params from ty2
-> Condition grp lat with db params from
Operator ty1 ty2 ('Null 'PGbool)
?
(ByteString -> Expression grp lat with db params from ty2
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression (ByteString -> Expression grp lat with db params from ty2)
-> ByteString -> Expression grp lat with db params from ty2
forall a b. (a -> b) -> a -> b
$ ByteString
"ANY" ByteString -> ByteString -> ByteString
<+> ByteString -> ByteString
parenthesized (Query (Join lat from) with db params '[col ::: ty2] -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Query (Join lat from) with db params '[col ::: ty2]
qry))
in_
:: Expression grp lat with db params from ty
-> [Expression grp lat with db params from ty]
-> Expression grp lat with db params from ('Null 'PGbool)
Expression grp lat with db params from ty
_ in_ :: Expression grp lat with db params from ty
-> [Expression grp lat with db params from ty]
-> Expression grp lat with db params from ('Null 'PGbool)
`in_` [] = Expression grp lat with db params from ('Null 'PGbool)
forall (null :: PGType -> NullType). Expr (null 'PGbool)
false
Expression grp lat with db params from ty
expr `in_` [Expression grp lat with db params from ty]
exprs = ByteString
-> Expression grp lat with db params from ('Null 'PGbool)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression (ByteString
-> Expression grp lat with db params from ('Null 'PGbool))
-> ByteString
-> Expression grp lat with db params from ('Null 'PGbool)
forall a b. (a -> b) -> a -> b
$ Expression grp lat with db params from ty -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Expression grp lat with db params from ty
expr ByteString -> ByteString -> ByteString
<+> ByteString
"IN"
ByteString -> ByteString -> ByteString
<+> ByteString -> ByteString
parenthesized ([ByteString] -> ByteString
commaSeparated (Expression grp lat with db params from ty -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL (Expression grp lat with db params from ty -> ByteString)
-> [Expression grp lat with db params from ty] -> [ByteString]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Expression grp lat with db params from ty]
exprs))
notIn
:: Expression grp lat with db params from ty
-> [Expression grp lat with db params from ty]
-> Expression grp lat with db params from ('Null 'PGbool)
Expression grp lat with db params from ty
_ notIn :: Expression grp lat with db params from ty
-> [Expression grp lat with db params from ty]
-> Expression grp lat with db params from ('Null 'PGbool)
`notIn` [] = Expression grp lat with db params from ('Null 'PGbool)
forall (null :: PGType -> NullType). Expr (null 'PGbool)
true
Expression grp lat with db params from ty
expr `notIn` [Expression grp lat with db params from ty]
exprs = ByteString
-> Expression grp lat with db params from ('Null 'PGbool)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression (ByteString
-> Expression grp lat with db params from ('Null 'PGbool))
-> ByteString
-> Expression grp lat with db params from ('Null 'PGbool)
forall a b. (a -> b) -> a -> b
$ Expression grp lat with db params from ty -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Expression grp lat with db params from ty
expr ByteString -> ByteString -> ByteString
<+> ByteString
"NOT IN"
ByteString -> ByteString -> ByteString
<+> ByteString -> ByteString
parenthesized ([ByteString] -> ByteString
commaSeparated (Expression grp lat with db params from ty -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL (Expression grp lat with db params from ty -> ByteString)
-> [Expression grp lat with db params from ty] -> [ByteString]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Expression grp lat with db params from ty]
exprs))