{-# LANGUAGE
AllowAmbiguousTypes
, DataKinds
, FlexibleContexts
, FlexibleInstances
, MultiParamTypeClasses
, OverloadedLabels
, OverloadedStrings
, RankNTypes
, ScopedTypeVariables
, TypeApplications
, TypeFamilies
, TypeOperators
, UndecidableInstances
#-}
module Squeal.PostgreSQL.Expression.Composite
(
row
, rowStar
, field
) where
import qualified Generics.SOP as SOP
import Squeal.PostgreSQL.Type.Alias
import Squeal.PostgreSQL.Expression
import Squeal.PostgreSQL.Type.List
import Squeal.PostgreSQL.Render
import Squeal.PostgreSQL.Type.Schema
row
:: SOP.SListI row
=> NP (Aliased (Expression grp lat with db params from)) row
-> Expression grp lat with db params from (null ('PGcomposite row))
row :: NP (Aliased (Expression grp lat with db params from)) row
-> Expression grp lat with db params from (null ('PGcomposite row))
row NP (Aliased (Expression grp lat with db params from)) row
exprs = ByteString
-> Expression grp lat with db params from (null ('PGcomposite row))
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 ('PGcomposite row)))
-> ByteString
-> Expression grp lat with db params from (null ('PGcomposite row))
forall a b. (a -> b) -> a -> b
$ ByteString
"ROW" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString -> ByteString
parenthesized
((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 (\ (expr `As` _) -> 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) NP (Aliased (Expression grp lat with db params from)) row
exprs)
rowStar
:: Has tab from row
=> Alias tab
-> Expression grp lat with db params from (null ('PGcomposite row))
rowStar :: Alias tab
-> Expression grp lat with db params from (null ('PGcomposite row))
rowStar Alias tab
tab = ByteString
-> Expression grp lat with db params from (null ('PGcomposite row))
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 ('PGcomposite row)))
-> ByteString
-> Expression grp lat with db params from (null ('PGcomposite row))
forall a b. (a -> b) -> a -> b
$ ByteString
"ROW" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<>
ByteString -> ByteString
parenthesized (Alias tab -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Alias tab
tab ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
".*")
field
:: ( relss ~ DbRelations db
, Has sch relss rels
, Has rel rels row
, Has field row ty
)
=> QualifiedAlias sch rel
-> Alias field
-> Expression grp lat with db params from ('NotNull ('PGcomposite row))
-> Expression grp lat with db params from ty
field :: QualifiedAlias sch rel
-> Alias field
-> Expression
grp lat with db params from ('NotNull ('PGcomposite row))
-> Expression grp lat with db params from ty
field QualifiedAlias sch rel
rel Alias field
fld Expression
grp lat with db params from ('NotNull ('PGcomposite row))
expr = ByteString -> Expression grp lat with db params from ty
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 ty)
-> ByteString -> Expression grp lat with db params from ty
forall a b. (a -> b) -> a -> b
$
ByteString -> ByteString
parenthesized (Expression
grp lat with db params from ('NotNull ('PGcomposite row))
-> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Expression
grp lat with db params from ('NotNull ('PGcomposite row))
expr ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
"::" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> QualifiedAlias sch rel -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL QualifiedAlias sch rel
rel)
ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
"." ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Alias field -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Alias field
fld