{-# LANGUAGE
ConstraintKinds
, DeriveGeneric
, DerivingStrategies
, FlexibleContexts
, FlexibleInstances
, GADTs
, GeneralizedNewtypeDeriving
, LambdaCase
, MultiParamTypeClasses
, OverloadedLabels
, OverloadedStrings
, QuantifiedConstraints
, ScopedTypeVariables
, StandaloneDeriving
, TypeApplications
, TypeFamilies
, DataKinds
, PolyKinds
, TypeOperators
, RankNTypes
, UndecidableInstances
#-}
module Squeal.PostgreSQL.Query.From
(
FromClause (..)
, table
, subquery
, view
, common
) where
import Control.DeepSeq
import Data.ByteString (ByteString)
import qualified GHC.Generics as GHC
import Squeal.PostgreSQL.Type.Alias
import Squeal.PostgreSQL.Query
import Squeal.PostgreSQL.Render
import Squeal.PostgreSQL.Type.List
import Squeal.PostgreSQL.Type.Schema
newtype FromClause
(lat :: FromType)
(with :: FromType)
(db :: SchemasType)
(params :: [NullType])
(from :: FromType)
= UnsafeFromClause { forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
FromClause lat with db params from -> ByteString
renderFromClause :: ByteString }
deriving stock (forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType) x.
Rep (FromClause lat with db params from) x
-> FromClause lat with db params from
forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType) x.
FromClause lat with db params from
-> Rep (FromClause lat with db params from) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType) x.
Rep (FromClause lat with db params from) x
-> FromClause lat with db params from
$cfrom :: forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType) x.
FromClause lat with db params from
-> Rep (FromClause lat with db params from) x
GHC.Generic,Int -> FromClause lat with db params from -> ShowS
forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
Int -> FromClause lat with db params from -> ShowS
forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
[FromClause lat with db params from] -> ShowS
forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
FromClause lat with db params from -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FromClause lat with db params from] -> ShowS
$cshowList :: forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
[FromClause lat with db params from] -> ShowS
show :: FromClause lat with db params from -> String
$cshow :: forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
FromClause lat with db params from -> String
showsPrec :: Int -> FromClause lat with db params from -> ShowS
$cshowsPrec :: forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
Int -> FromClause lat with db params from -> ShowS
Show,FromClause lat with db params from
-> FromClause lat with db params from -> Bool
forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
FromClause lat with db params from
-> FromClause lat with db params from -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FromClause lat with db params from
-> FromClause lat with db params from -> Bool
$c/= :: forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
FromClause lat with db params from
-> FromClause lat with db params from -> Bool
== :: FromClause lat with db params from
-> FromClause lat with db params from -> Bool
$c== :: forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
FromClause lat with db params from
-> FromClause lat with db params from -> Bool
Eq,FromClause lat with db params from
-> FromClause lat with db params from -> Bool
FromClause lat with db params from
-> FromClause lat with db params from -> Ordering
forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
Eq (FromClause lat with db params from)
forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
FromClause lat with db params from
-> FromClause lat with db params from -> Bool
forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
FromClause lat with db params from
-> FromClause lat with db params from -> Ordering
forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
FromClause lat with db params from
-> FromClause lat with db params from
-> FromClause lat with db params from
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FromClause lat with db params from
-> FromClause lat with db params from
-> FromClause lat with db params from
$cmin :: forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
FromClause lat with db params from
-> FromClause lat with db params from
-> FromClause lat with db params from
max :: FromClause lat with db params from
-> FromClause lat with db params from
-> FromClause lat with db params from
$cmax :: forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
FromClause lat with db params from
-> FromClause lat with db params from
-> FromClause lat with db params from
>= :: FromClause lat with db params from
-> FromClause lat with db params from -> Bool
$c>= :: forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
FromClause lat with db params from
-> FromClause lat with db params from -> Bool
> :: FromClause lat with db params from
-> FromClause lat with db params from -> Bool
$c> :: forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
FromClause lat with db params from
-> FromClause lat with db params from -> Bool
<= :: FromClause lat with db params from
-> FromClause lat with db params from -> Bool
$c<= :: forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
FromClause lat with db params from
-> FromClause lat with db params from -> Bool
< :: FromClause lat with db params from
-> FromClause lat with db params from -> Bool
$c< :: forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
FromClause lat with db params from
-> FromClause lat with db params from -> Bool
compare :: FromClause lat with db params from
-> FromClause lat with db params from -> Ordering
$ccompare :: forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
FromClause lat with db params from
-> FromClause lat with db params from -> Ordering
Ord)
deriving newtype (FromClause lat with db params from -> ()
forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
FromClause lat with db params from -> ()
forall a. (a -> ()) -> NFData a
rnf :: FromClause lat with db params from -> ()
$crnf :: forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
FromClause lat with db params from -> ()
NFData)
instance RenderSQL (FromClause lat with db params from) where
renderSQL :: FromClause lat with db params from -> ByteString
renderSQL = forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
FromClause lat with db params from -> ByteString
renderFromClause
table
:: (Has sch db schema, Has tab schema ('Table table))
=> Aliased (QualifiedAlias sch) (alias ::: tab)
-> FromClause lat with db params '[alias ::: TableToRow table]
table :: forall (sch :: Symbol) (db :: SchemasType)
(schema :: [(Symbol, SchemumType)]) (tab :: Symbol)
(table :: TableType) (alias :: Symbol) (lat :: FromType)
(with :: FromType) (params :: [NullType]).
(Has sch db schema, Has tab schema ('Table table)) =>
Aliased (QualifiedAlias sch) (alias ::: tab)
-> FromClause lat with db params '[alias ::: TableToRow table]
table (QualifiedAlias sch ty
tab `As` Alias alias
alias) = forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
ByteString -> FromClause lat with db params from
UnsafeFromClause forall a b. (a -> b) -> a -> b
$
forall sql. RenderSQL sql => sql -> ByteString
renderSQL QualifiedAlias sch ty
tab ByteString -> ByteString -> ByteString
<+> ByteString
"AS" ByteString -> ByteString -> ByteString
<+> forall sql. RenderSQL sql => sql -> ByteString
renderSQL Alias alias
alias
subquery
:: Aliased (Query lat with db params) query
-> FromClause lat with db params '[query]
subquery :: forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (query :: (Symbol, RowType)).
Aliased (Query lat with db params) query
-> FromClause lat with db params '[query]
subquery = forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
ByteString -> FromClause lat with db params from
UnsafeFromClause forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {k} (expression :: k -> *) (aliased :: (Symbol, k)).
(forall (ty :: k). expression ty -> ByteString)
-> Aliased expression aliased -> ByteString
renderAliased (ByteString -> ByteString
parenthesized forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall sql. RenderSQL sql => sql -> ByteString
renderSQL)
view
:: (Has sch db schema, Has vw schema ('View view))
=> Aliased (QualifiedAlias sch) (alias ::: vw)
-> FromClause lat with db params '[alias ::: view]
view :: forall (sch :: Symbol) (db :: SchemasType)
(schema :: [(Symbol, SchemumType)]) (vw :: Symbol)
(view :: RowType) (alias :: Symbol) (lat :: FromType)
(with :: FromType) (params :: [NullType]).
(Has sch db schema, Has vw schema ('View view)) =>
Aliased (QualifiedAlias sch) (alias ::: vw)
-> FromClause lat with db params '[alias ::: view]
view (QualifiedAlias sch ty
vw `As` Alias alias
alias) = forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
ByteString -> FromClause lat with db params from
UnsafeFromClause forall a b. (a -> b) -> a -> b
$
forall sql. RenderSQL sql => sql -> ByteString
renderSQL QualifiedAlias sch ty
vw ByteString -> ByteString -> ByteString
<+> ByteString
"AS" ByteString -> ByteString -> ByteString
<+> forall sql. RenderSQL sql => sql -> ByteString
renderSQL Alias alias
alias
common
:: Has cte with common
=> Aliased Alias (alias ::: cte)
-> FromClause lat with db params '[alias ::: common]
common :: forall (cte :: Symbol) (with :: FromType) (common :: RowType)
(alias :: Symbol) (lat :: FromType) (db :: SchemasType)
(params :: [NullType]).
Has cte with common =>
Aliased Alias (alias ::: cte)
-> FromClause lat with db params '[alias ::: common]
common (Alias ty
cte `As` Alias alias
alias) = forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
ByteString -> FromClause lat with db params from
UnsafeFromClause forall a b. (a -> b) -> a -> b
$
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Alias ty
cte ByteString -> ByteString -> ByteString
<+> ByteString
"AS" ByteString -> ByteString -> ByteString
<+> forall sql. RenderSQL sql => sql -> ByteString
renderSQL Alias alias
alias
instance Additional (FromClause lat with db params) where
also :: forall (ys :: FromType) (xs :: FromType).
FromClause lat with db params ys
-> FromClause lat with db params xs
-> FromClause lat with db params (Join xs ys)
also FromClause lat with db params ys
right FromClause lat with db params xs
left = forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
ByteString -> FromClause lat with db params from
UnsafeFromClause forall a b. (a -> b) -> a -> b
$
forall sql. RenderSQL sql => sql -> ByteString
renderSQL FromClause lat with db params xs
left forall a. Semigroup a => a -> a -> a
<> ByteString
", " forall a. Semigroup a => a -> a -> a
<> forall sql. RenderSQL sql => sql -> ByteString
renderSQL FromClause lat with db params ys
right