{-# LANGUAGE
ConstraintKinds
, DeriveGeneric
, DerivingStrategies
, FlexibleContexts
, FlexibleInstances
, GADTs
, GeneralizedNewtypeDeriving
, LambdaCase
, MultiParamTypeClasses
, OverloadedLabels
, OverloadedStrings
, QuantifiedConstraints
, ScopedTypeVariables
, StandaloneDeriving
, TypeApplications
, TypeFamilies
, TypeInType
, TypeOperators
, RankNTypes
, UndecidableInstances
#-}
module Squeal.PostgreSQL.Query.Select
(
select
, select_
, selectDistinct
, selectDistinct_
, selectDistinctOn
, selectDistinctOn_
, Selection (..)
) where
import Data.ByteString (ByteString)
import Data.String
import Generics.SOP hiding (from)
import GHC.TypeLits
import Squeal.PostgreSQL.Type.Alias
import Squeal.PostgreSQL.Expression
import Squeal.PostgreSQL.Expression.Sort
import Squeal.PostgreSQL.Expression.Window
import Squeal.PostgreSQL.Query
import Squeal.PostgreSQL.Query.Table
import Squeal.PostgreSQL.Type.List
import Squeal.PostgreSQL.Render
import Squeal.PostgreSQL.Type.Schema
data Selection grp lat with db params from row where
Star
:: HasUnique tab from row
=> Selection 'Ungrouped lat with db params from row
DotStar
:: Has tab from row
=> Alias tab
-> Selection 'Ungrouped lat with db params from row
List
:: SListI row
=> NP (Aliased (Expression grp lat with db params from)) row
-> Selection grp lat with db params from row
Over
:: SListI row
=> NP (Aliased (WindowFunction grp lat with db params from)) row
-> WindowDefinition grp lat with db params from
-> Selection grp lat with db params from row
Also
:: Selection grp lat with db params from right
-> Selection grp lat with db params from left
-> Selection grp lat with db params from (Join left right)
instance Additional (Selection grp lat with db params from) where
also :: Selection grp lat with db params from ys
-> Selection grp lat with db params from xs
-> Selection grp lat with db params from (Join xs ys)
also = Selection grp lat with db params from ys
-> Selection grp lat with db params from xs
-> Selection grp lat with db params from (Join xs ys)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ys :: [(Symbol, NullType)]) (xs :: [(Symbol, NullType)]).
Selection grp lat with db params from ys
-> Selection grp lat with db params from xs
-> Selection grp lat with db params from (Join xs ys)
Also
instance (KnownSymbol col, row ~ '[col ::: ty])
=> Aliasable col
(Expression grp lat with db params from ty)
(Selection grp lat with db params from row) where
Expression grp lat with db params from ty
expr `as` Alias col
col = NP (Aliased (Expression grp lat with db params from)) row
-> Selection grp lat with db params from row
forall (row :: [(Symbol, NullType)]) (grp :: Grouping)
(lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
SListI row =>
NP (Aliased (Expression grp lat with db params from)) row
-> Selection grp lat with db params from row
List (Expression grp lat with db params from ty
expr `as` Alias col
col)
instance (Has tab (Join from lat) row0, Has col row0 ty, row1 ~ '[col ::: ty])
=> IsQualified tab col
(Selection 'Ungrouped lat with db params from row1) where
Alias tab
tab ! :: Alias tab
-> Alias col -> Selection 'Ungrouped lat with db params from row1
! Alias col
col = Alias tab
tab Alias tab
-> Alias col -> Expression 'Ungrouped lat with db params from ty
forall (qualifier :: Symbol) (alias :: Symbol) expression.
IsQualified qualifier alias expression =>
Alias qualifier -> Alias alias -> expression
! Alias col
col `as` Alias col
col
instance
( Has tab (Join from lat) row0
, Has col row0 ty
, row1 ~ '[col ::: ty]
, GroupedBy tab col bys )
=> IsQualified tab col
(Selection ('Grouped bys) lat with db params from row1) where
Alias tab
tab ! :: Alias tab
-> Alias col
-> Selection ('Grouped bys) lat with db params from row1
! Alias col
col = Alias tab
tab Alias tab
-> Alias col
-> Expression ('Grouped bys) lat with db params from ty
forall (qualifier :: Symbol) (alias :: Symbol) expression.
IsQualified qualifier alias expression =>
Alias qualifier -> Alias alias -> expression
! Alias col
col `as` Alias col
col
instance (HasUnique tab (Join from lat) row0, Has col row0 ty, row1 ~ '[col ::: ty])
=> IsLabel col
(Selection 'Ungrouped lat with db params from row1) where
fromLabel :: Selection 'Ungrouped lat with db params from row1
fromLabel = forall a. IsLabel col a => a
forall (x :: Symbol) a. IsLabel x a => a
fromLabel @col `as` Alias col
forall (alias :: Symbol). Alias alias
Alias
instance
( HasUnique tab (Join from lat) row0
, Has col row0 ty
, row1 ~ '[col ::: ty]
, GroupedBy tab col bys )
=> IsLabel col
(Selection ('Grouped bys) lat with db params from row1) where
fromLabel :: Selection ('Grouped bys) lat with db params from row1
fromLabel = forall a. IsLabel col a => a
forall (x :: Symbol) a. IsLabel x a => a
fromLabel @col `as` Alias col
forall (alias :: Symbol). Alias alias
Alias
instance RenderSQL (Selection grp lat with db params from row) where
renderSQL :: Selection grp lat with db params from row -> ByteString
renderSQL = \case
List NP (Aliased (Expression grp lat with db params from)) row
list -> (forall (x :: (Symbol, NullType)).
Aliased (Expression grp lat with db params from) x -> ByteString)
-> NP (Aliased (Expression grp lat with db params from)) row
-> ByteString
forall k (xs :: [k]) (expression :: k -> *).
SListI xs =>
(forall (x :: k). expression x -> ByteString)
-> NP expression xs -> ByteString
renderCommaSeparated ((forall (ty :: NullType).
Expression grp lat with db params from ty -> ByteString)
-> Aliased (Expression grp lat with db params from) x -> ByteString
forall k (expression :: k -> *) (aliased :: (Symbol, k)).
(forall (ty :: k). expression ty -> ByteString)
-> Aliased expression aliased -> ByteString
renderAliased forall sql. RenderSQL sql => sql -> ByteString
forall (ty :: NullType).
Expression grp lat with db params from ty -> ByteString
renderSQL) NP (Aliased (Expression grp lat with db params from)) row
list
Selection grp lat with db params from row
Star -> ByteString
"*"
DotStar Alias tab
tab -> Alias tab -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Alias tab
tab ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
".*"
Also Selection grp lat with db params from right
right Selection grp lat with db params from left
left -> Selection grp lat with db params from left -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Selection grp lat with db params from left
left ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
", " ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Selection grp lat with db params from right -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Selection grp lat with db params from right
right
Over NP (Aliased (WindowFunction grp lat with db params from)) row
winFns WindowDefinition grp lat with db params from
winDef ->
let
renderOver
:: Aliased (WindowFunction grp lat with db params from) field
-> ByteString
renderOver :: Aliased (WindowFunction grp lat with db params from) field
-> ByteString
renderOver (WindowFunction grp lat with db params from ty
winFn `As` Alias alias
col) = WindowFunction grp lat with db params from ty -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL WindowFunction grp lat with db params from ty
winFn
ByteString -> ByteString -> ByteString
<+> ByteString
"OVER" ByteString -> ByteString -> ByteString
<+> ByteString -> ByteString
parenthesized (WindowDefinition grp lat with db params from -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL WindowDefinition grp lat with db params from
winDef)
ByteString -> ByteString -> ByteString
<+> ByteString
"AS" ByteString -> ByteString -> ByteString
<+> Alias alias -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Alias alias
col
in
(forall (x :: (Symbol, NullType)).
Aliased (WindowFunction grp lat with db params from) x
-> ByteString)
-> NP (Aliased (WindowFunction grp lat with db params from)) row
-> ByteString
forall k (xs :: [k]) (expression :: k -> *).
SListI xs =>
(forall (x :: k). expression x -> ByteString)
-> NP expression xs -> ByteString
renderCommaSeparated forall (x :: (Symbol, NullType)).
Aliased (WindowFunction grp lat with db params from) x
-> ByteString
renderOver NP (Aliased (WindowFunction grp lat with db params from)) row
winFns
instance IsString
(Selection grp lat with db params from '["fromOnly" ::: 'NotNull 'PGtext]) where
fromString :: String
-> Selection
grp lat with db params from '["fromOnly" ::: 'NotNull 'PGtext]
fromString String
str = String -> Expression grp lat with db params from ('NotNull 'PGtext)
forall a. IsString a => String -> a
fromString String
str `as` Alias "fromOnly"
forall (alias :: Symbol). Alias alias
Alias
select
:: (SListI row, row ~ (x ': xs))
=> Selection grp lat with db params from row
-> TableExpression grp lat with db params from
-> Query lat with db params row
select :: Selection grp lat with db params from row
-> TableExpression grp lat with db params from
-> Query lat with db params row
select Selection grp lat with db params from row
selection TableExpression grp lat with db params from
tabexpr = ByteString -> Query lat with db params row
forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (row :: [(Symbol, NullType)]).
ByteString -> Query lat with db params row
UnsafeQuery (ByteString -> Query lat with db params row)
-> ByteString -> Query lat with db params row
forall a b. (a -> b) -> a -> b
$
ByteString
"SELECT"
ByteString -> ByteString -> ByteString
<+> Selection grp lat with db params from row -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Selection grp lat with db params from row
selection
ByteString -> ByteString -> ByteString
<+> TableExpression grp lat with db params from -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL TableExpression grp lat with db params from
tabexpr
select_
:: (SListI row, row ~ (x ': xs))
=> NP (Aliased (Expression grp lat with db params from)) row
-> TableExpression grp lat with db params from
-> Query lat with db params row
select_ :: NP (Aliased (Expression grp lat with db params from)) row
-> TableExpression grp lat with db params from
-> Query lat with db params row
select_ = Selection grp lat with db params from row
-> TableExpression grp lat with db params from
-> Query lat with db params row
forall (row :: [(Symbol, NullType)]) (x :: (Symbol, NullType))
(xs :: [(Symbol, NullType)]) (grp :: Grouping) (lat :: FromType)
(with :: FromType) (db :: SchemasType) (params :: [NullType])
(from :: FromType).
(SListI row, row ~ (x : xs)) =>
Selection grp lat with db params from row
-> TableExpression grp lat with db params from
-> Query lat with db params row
select (Selection grp lat with db params from row
-> TableExpression grp lat with db params from
-> Query lat with db params row)
-> (NP (Aliased (Expression grp lat with db params from)) row
-> Selection grp lat with db params from row)
-> NP (Aliased (Expression grp lat with db params from)) row
-> TableExpression grp lat with db params from
-> Query lat with db params row
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NP (Aliased (Expression grp lat with db params from)) row
-> Selection grp lat with db params from row
forall (row :: [(Symbol, NullType)]) (grp :: Grouping)
(lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
SListI row =>
NP (Aliased (Expression grp lat with db params from)) row
-> Selection grp lat with db params from row
List
selectDistinct
:: (SListI columns, columns ~ (col ': cols))
=> Selection grp lat with db params from columns
-> TableExpression grp lat with db params from
-> Query lat with db params columns
selectDistinct :: Selection grp lat with db params from columns
-> TableExpression grp lat with db params from
-> Query lat with db params columns
selectDistinct Selection grp lat with db params from columns
selection TableExpression grp lat with db params from
tabexpr = ByteString -> Query lat with db params columns
forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (row :: [(Symbol, NullType)]).
ByteString -> Query lat with db params row
UnsafeQuery (ByteString -> Query lat with db params columns)
-> ByteString -> Query lat with db params columns
forall a b. (a -> b) -> a -> b
$
ByteString
"SELECT DISTINCT"
ByteString -> ByteString -> ByteString
<+> Selection grp lat with db params from columns -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Selection grp lat with db params from columns
selection
ByteString -> ByteString -> ByteString
<+> TableExpression grp lat with db params from -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL TableExpression grp lat with db params from
tabexpr
selectDistinct_
:: (SListI columns, columns ~ (col ': cols))
=> NP (Aliased (Expression grp lat with db params from)) columns
-> TableExpression grp lat with db params from
-> Query lat with db params columns
selectDistinct_ :: NP (Aliased (Expression grp lat with db params from)) columns
-> TableExpression grp lat with db params from
-> Query lat with db params columns
selectDistinct_ = Selection grp lat with db params from columns
-> TableExpression grp lat with db params from
-> Query lat with db params columns
forall (row :: [(Symbol, NullType)]) (x :: (Symbol, NullType))
(xs :: [(Symbol, NullType)]) (grp :: Grouping) (lat :: FromType)
(with :: FromType) (db :: SchemasType) (params :: [NullType])
(from :: FromType).
(SListI row, row ~ (x : xs)) =>
Selection grp lat with db params from row
-> TableExpression grp lat with db params from
-> Query lat with db params row
selectDistinct (Selection grp lat with db params from columns
-> TableExpression grp lat with db params from
-> Query lat with db params columns)
-> (NP (Aliased (Expression grp lat with db params from)) columns
-> Selection grp lat with db params from columns)
-> NP (Aliased (Expression grp lat with db params from)) columns
-> TableExpression grp lat with db params from
-> Query lat with db params columns
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NP (Aliased (Expression grp lat with db params from)) columns
-> Selection grp lat with db params from columns
forall (row :: [(Symbol, NullType)]) (grp :: Grouping)
(lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
SListI row =>
NP (Aliased (Expression grp lat with db params from)) row
-> Selection grp lat with db params from row
List
selectDistinctOn
:: (SListI columns, columns ~ (col ': cols))
=> [SortExpression grp lat with db params from]
-> Selection grp lat with db params from columns
-> TableExpression grp lat with db params from
-> Query lat with db params columns
selectDistinctOn :: [SortExpression grp lat with db params from]
-> Selection grp lat with db params from columns
-> TableExpression grp lat with db params from
-> Query lat with db params columns
selectDistinctOn [SortExpression grp lat with db params from]
distincts Selection grp lat with db params from columns
selection TableExpression grp lat with db params from
tab = ByteString -> Query lat with db params columns
forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (row :: [(Symbol, NullType)]).
ByteString -> Query lat with db params row
UnsafeQuery (ByteString -> Query lat with db params columns)
-> ByteString -> Query lat with db params columns
forall a b. (a -> b) -> a -> b
$
ByteString
"SELECT DISTINCT ON"
ByteString -> ByteString -> ByteString
<+> ByteString -> ByteString
parenthesized ([ByteString] -> ByteString
commaSeparated (SortExpression grp lat with db params from -> ByteString
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType).
SortExpression grp lat with db params from -> ByteString
renderDistinctOn (SortExpression grp lat with db params from -> ByteString)
-> [SortExpression grp lat with db params from] -> [ByteString]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [SortExpression grp lat with db params from]
distincts))
ByteString -> ByteString -> ByteString
<+> Selection grp lat with db params from columns -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Selection grp lat with db params from columns
selection
ByteString -> ByteString -> ByteString
<+> TableExpression grp lat with db params from -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL (TableExpression grp lat with db params from
tab {orderByClause :: [SortExpression grp lat with db params from]
orderByClause = [SortExpression grp lat with db params from]
distincts [SortExpression grp lat with db params from]
-> [SortExpression grp lat with db params from]
-> [SortExpression grp lat with db params from]
forall a. Semigroup a => a -> a -> a
<> TableExpression grp lat with db params from
-> [SortExpression grp lat with db params from]
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType).
TableExpression grp lat with db params from
-> [SortExpression grp lat with db params from]
orderByClause TableExpression grp lat with db params from
tab})
where
renderDistinctOn :: SortExpression grp lat with db params from -> ByteString
renderDistinctOn = \case
Asc Expression grp lat with db params from ('NotNull ty)
expression -> Expression grp lat with db params from ('NotNull ty) -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Expression grp lat with db params from ('NotNull ty)
expression
Desc Expression grp lat with db params from ('NotNull ty)
expression -> Expression grp lat with db params from ('NotNull ty) -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Expression grp lat with db params from ('NotNull ty)
expression
AscNullsFirst Expression grp lat with db params from ('Null ty)
expression -> Expression grp lat with db params from ('Null ty) -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Expression grp lat with db params from ('Null ty)
expression
DescNullsFirst Expression grp lat with db params from ('Null ty)
expression -> Expression grp lat with db params from ('Null ty) -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Expression grp lat with db params from ('Null ty)
expression
AscNullsLast Expression grp lat with db params from ('Null ty)
expression -> Expression grp lat with db params from ('Null ty) -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Expression grp lat with db params from ('Null ty)
expression
DescNullsLast Expression grp lat with db params from ('Null ty)
expression -> Expression grp lat with db params from ('Null ty) -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Expression grp lat with db params from ('Null ty)
expression
selectDistinctOn_
:: (SListI columns, columns ~ (col ': cols))
=> [SortExpression grp lat with db params from]
-> NP (Aliased (Expression grp lat with db params from)) columns
-> TableExpression grp lat with db params from
-> Query lat with db params columns
selectDistinctOn_ :: [SortExpression grp lat with db params from]
-> NP (Aliased (Expression grp lat with db params from)) columns
-> TableExpression grp lat with db params from
-> Query lat with db params columns
selectDistinctOn_ [SortExpression grp lat with db params from]
distincts = [SortExpression grp lat with db params from]
-> Selection grp lat with db params from columns
-> TableExpression grp lat with db params from
-> Query lat with db params columns
forall (columns :: [(Symbol, NullType)])
(col :: (Symbol, NullType)) (cols :: [(Symbol, NullType)])
(grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType).
(SListI columns, columns ~ (col : cols)) =>
[SortExpression grp lat with db params from]
-> Selection grp lat with db params from columns
-> TableExpression grp lat with db params from
-> Query lat with db params columns
selectDistinctOn [SortExpression grp lat with db params from]
distincts (Selection grp lat with db params from columns
-> TableExpression grp lat with db params from
-> Query lat with db params columns)
-> (NP (Aliased (Expression grp lat with db params from)) columns
-> Selection grp lat with db params from columns)
-> NP (Aliased (Expression grp lat with db params from)) columns
-> TableExpression grp lat with db params from
-> Query lat with db params columns
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NP (Aliased (Expression grp lat with db params from)) columns
-> Selection grp lat with db params from columns
forall (row :: [(Symbol, NullType)]) (grp :: Grouping)
(lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
SListI row =>
NP (Aliased (Expression grp lat with db params from)) row
-> Selection grp lat with db params from row
List