{-# LANGUAGE
DeriveGeneric
, DerivingStrategies
, FlexibleContexts
, FlexibleInstances
, GADTs
, GeneralizedNewtypeDeriving
, LambdaCase
, MultiParamTypeClasses
, OverloadedStrings
, PatternSynonyms
, QuantifiedConstraints
, RankNTypes
, ScopedTypeVariables
, TypeApplications
, TypeFamilies
, TypeInType
, TypeOperators
, UndecidableInstances
#-}
module Squeal.PostgreSQL.Manipulation.Delete
(
deleteFrom
, deleteFrom_
) where
import qualified Generics.SOP as SOP
import Squeal.PostgreSQL.Type.Alias
import Squeal.PostgreSQL.Expression.Logic
import Squeal.PostgreSQL.Manipulation
import Squeal.PostgreSQL.Type.List
import Squeal.PostgreSQL.Render
import Squeal.PostgreSQL.Type.Schema
deleteFrom
:: ( SOP.SListI row
, Has sch db schema
, Has tab0 schema ('Table table) )
=> Aliased (QualifiedAlias sch) (tab ::: tab0)
-> UsingClause with db params from
-> Condition 'Ungrouped '[] with db params (tab ::: TableToRow table ': from)
-> ReturningClause with db params (tab ::: TableToRow table ': from) row
-> Manipulation with db params row
deleteFrom :: Aliased (QualifiedAlias sch) (tab ::: tab0)
-> UsingClause with db params from
-> Condition
'Ungrouped '[] with db params ((tab ::: TableToRow table) : from)
-> ReturningClause
with db params ((tab ::: TableToRow table) : from) row
-> Manipulation with db params row
deleteFrom (QualifiedAlias sch ty
tab0 `As` Alias alias
tab) UsingClause with db params from
using Condition
'Ungrouped '[] with db params ((tab ::: TableToRow table) : from)
wh ReturningClause
with db params ((tab ::: TableToRow table) : from) row
returning = ByteString -> Manipulation with db params row
forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType).
ByteString -> Manipulation with db params columns
UnsafeManipulation (ByteString -> Manipulation with db params row)
-> ByteString -> Manipulation with db params row
forall a b. (a -> b) -> a -> b
$
ByteString
"DELETE FROM"
ByteString -> ByteString -> ByteString
<+> QualifiedAlias sch ty -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL QualifiedAlias sch ty
tab0 ByteString -> ByteString -> ByteString
<+> ByteString
"AS" ByteString -> ByteString -> ByteString
<+> Alias alias -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Alias alias
tab
ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> case UsingClause with db params from
using of
UsingClause with db params from
NoUsing -> ByteString
""
Using FromClause '[] with db params from
tables -> ByteString
" USING" ByteString -> ByteString -> ByteString
<+> FromClause '[] with db params from -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL FromClause '[] with db params from
tables
ByteString -> ByteString -> ByteString
<+> ByteString
"WHERE" ByteString -> ByteString -> ByteString
<+> Condition
'Ungrouped
'[]
with
db
params
((tab ::: ColumnsToRow (TableToColumns table)) : from)
-> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Condition
'Ungrouped '[] with db params ((tab ::: TableToRow table) : from)
Condition
'Ungrouped
'[]
with
db
params
((tab ::: ColumnsToRow (TableToColumns table)) : from)
wh
ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ReturningClause
with
db
params
((tab ::: ColumnsToRow (TableToColumns table)) : from)
row
-> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL ReturningClause
with db params ((tab ::: TableToRow table) : from) row
ReturningClause
with
db
params
((tab ::: ColumnsToRow (TableToColumns table)) : from)
row
returning
deleteFrom_
:: ( Has sch db schema
, Has tab0 schema ('Table table) )
=> Aliased (QualifiedAlias sch) (tab ::: tab0)
-> Condition 'Ungrouped '[] with db params '[tab ::: TableToRow table]
-> Manipulation with db params '[]
deleteFrom_ :: Aliased (QualifiedAlias sch) (tab ::: tab0)
-> Condition
'Ungrouped '[] with db params '[tab ::: TableToRow table]
-> Manipulation with db params '[]
deleteFrom_ Aliased (QualifiedAlias sch) (tab ::: tab0)
tab Condition 'Ungrouped '[] with db params '[tab ::: TableToRow table]
wh = Aliased (QualifiedAlias sch) (tab ::: tab0)
-> UsingClause with db params '[]
-> Condition
'Ungrouped '[] with db params '[tab ::: TableToRow table]
-> ReturningClause with db params '[tab ::: TableToRow table] '[]
-> Manipulation with db params '[]
forall (row :: RowType) (sch :: Symbol) (db :: SchemasType)
(schema :: [(Symbol, SchemumType)]) (tab0 :: Symbol)
(table :: TableType) (tab :: Symbol) (with :: FromType)
(params :: [NullType]) (from :: FromType).
(SListI row, Has sch db schema, Has tab0 schema ('Table table)) =>
Aliased (QualifiedAlias sch) (tab ::: tab0)
-> UsingClause with db params from
-> Condition
'Ungrouped '[] with db params ((tab ::: TableToRow table) : from)
-> ReturningClause
with db params ((tab ::: TableToRow table) : from) row
-> Manipulation with db params row
deleteFrom Aliased (QualifiedAlias sch) (tab ::: tab0)
tab UsingClause with db params '[]
forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]).
UsingClause with db params '[]
NoUsing Condition 'Ungrouped '[] with db params '[tab ::: TableToRow table]
wh (NP
(Aliased
(Expression
'Ungrouped
'[]
with
db
params
'[tab ::: ColumnsToRow (TableToColumns table)]))
'[]
-> ReturningClause
with db params '[tab ::: ColumnsToRow (TableToColumns table)] '[]
forall (row :: RowType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
SListI row =>
NP (Aliased (Expression 'Ungrouped '[] with db params from)) row
-> ReturningClause with db params from row
Returning_ NP
(Aliased
(Expression
'Ungrouped
'[]
with
db
params
'[tab ::: ColumnsToRow (TableToColumns table)]))
'[]
forall k (a :: k -> *). NP a '[]
Nil)