{-# LANGUAGE
DeriveGeneric
, DerivingStrategies
, FlexibleContexts
, FlexibleInstances
, GADTs
, GeneralizedNewtypeDeriving
, LambdaCase
, MultiParamTypeClasses
, OverloadedStrings
, PatternSynonyms
, QuantifiedConstraints
, RankNTypes
, ScopedTypeVariables
, TypeApplications
, TypeFamilies
, TypeInType
, TypeOperators
, UndecidableInstances
#-}
module Squeal.PostgreSQL.Manipulation
(
Manipulation (..)
, Manipulation_
, queryStatement
, ReturningClause (..)
, pattern Returning_
, UsingClause (..)
) where
import Control.DeepSeq
import Data.ByteString hiding (foldr)
import Data.Kind (Type)
import Data.Quiver.Functor
import qualified Generics.SOP as SOP
import qualified GHC.Generics as GHC
import Squeal.PostgreSQL.Type.Alias
import Squeal.PostgreSQL.Expression
import Squeal.PostgreSQL.Type.List
import Squeal.PostgreSQL.Type.PG
import Squeal.PostgreSQL.Render
import Squeal.PostgreSQL.Query
import Squeal.PostgreSQL.Query.From
import Squeal.PostgreSQL.Query.Select
import Squeal.PostgreSQL.Query.With
import Squeal.PostgreSQL.Type.Schema
newtype Manipulation
(with :: FromType)
(db :: SchemasType)
(params :: [NullType])
(columns :: RowType)
= UnsafeManipulation { Manipulation with db params columns -> ByteString
renderManipulation :: ByteString }
deriving stock ((forall x.
Manipulation with db params columns
-> Rep (Manipulation with db params columns) x)
-> (forall x.
Rep (Manipulation with db params columns) x
-> Manipulation with db params columns)
-> Generic (Manipulation with db params columns)
forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType) x.
Rep (Manipulation with db params columns) x
-> Manipulation with db params columns
forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType) x.
Manipulation with db params columns
-> Rep (Manipulation with db params columns) x
forall x.
Rep (Manipulation with db params columns) x
-> Manipulation with db params columns
forall x.
Manipulation with db params columns
-> Rep (Manipulation with db params columns) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType) x.
Rep (Manipulation with db params columns) x
-> Manipulation with db params columns
$cfrom :: forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType) x.
Manipulation with db params columns
-> Rep (Manipulation with db params columns) x
GHC.Generic,Int -> Manipulation with db params columns -> ShowS
[Manipulation with db params columns] -> ShowS
Manipulation with db params columns -> String
(Int -> Manipulation with db params columns -> ShowS)
-> (Manipulation with db params columns -> String)
-> ([Manipulation with db params columns] -> ShowS)
-> Show (Manipulation with db params columns)
forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType).
Int -> Manipulation with db params columns -> ShowS
forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType).
[Manipulation with db params columns] -> ShowS
forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType).
Manipulation with db params columns -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Manipulation with db params columns] -> ShowS
$cshowList :: forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType).
[Manipulation with db params columns] -> ShowS
show :: Manipulation with db params columns -> String
$cshow :: forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType).
Manipulation with db params columns -> String
showsPrec :: Int -> Manipulation with db params columns -> ShowS
$cshowsPrec :: forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType).
Int -> Manipulation with db params columns -> ShowS
Show,Manipulation with db params columns
-> Manipulation with db params columns -> Bool
(Manipulation with db params columns
-> Manipulation with db params columns -> Bool)
-> (Manipulation with db params columns
-> Manipulation with db params columns -> Bool)
-> Eq (Manipulation with db params columns)
forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType).
Manipulation with db params columns
-> Manipulation with db params columns -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Manipulation with db params columns
-> Manipulation with db params columns -> Bool
$c/= :: forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType).
Manipulation with db params columns
-> Manipulation with db params columns -> Bool
== :: Manipulation with db params columns
-> Manipulation with db params columns -> Bool
$c== :: forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType).
Manipulation with db params columns
-> Manipulation with db params columns -> Bool
Eq,Eq (Manipulation with db params columns)
Eq (Manipulation with db params columns)
-> (Manipulation with db params columns
-> Manipulation with db params columns -> Ordering)
-> (Manipulation with db params columns
-> Manipulation with db params columns -> Bool)
-> (Manipulation with db params columns
-> Manipulation with db params columns -> Bool)
-> (Manipulation with db params columns
-> Manipulation with db params columns -> Bool)
-> (Manipulation with db params columns
-> Manipulation with db params columns -> Bool)
-> (Manipulation with db params columns
-> Manipulation with db params columns
-> Manipulation with db params columns)
-> (Manipulation with db params columns
-> Manipulation with db params columns
-> Manipulation with db params columns)
-> Ord (Manipulation with db params columns)
Manipulation with db params columns
-> Manipulation with db params columns -> Bool
Manipulation with db params columns
-> Manipulation with db params columns -> Ordering
Manipulation with db params columns
-> Manipulation with db params columns
-> Manipulation with db params columns
forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType).
Eq (Manipulation with db params columns)
forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType).
Manipulation with db params columns
-> Manipulation with db params columns -> Bool
forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType).
Manipulation with db params columns
-> Manipulation with db params columns -> Ordering
forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType).
Manipulation with db params columns
-> Manipulation with db params columns
-> Manipulation with db params columns
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 :: Manipulation with db params columns
-> Manipulation with db params columns
-> Manipulation with db params columns
$cmin :: forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType).
Manipulation with db params columns
-> Manipulation with db params columns
-> Manipulation with db params columns
max :: Manipulation with db params columns
-> Manipulation with db params columns
-> Manipulation with db params columns
$cmax :: forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType).
Manipulation with db params columns
-> Manipulation with db params columns
-> Manipulation with db params columns
>= :: Manipulation with db params columns
-> Manipulation with db params columns -> Bool
$c>= :: forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType).
Manipulation with db params columns
-> Manipulation with db params columns -> Bool
> :: Manipulation with db params columns
-> Manipulation with db params columns -> Bool
$c> :: forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType).
Manipulation with db params columns
-> Manipulation with db params columns -> Bool
<= :: Manipulation with db params columns
-> Manipulation with db params columns -> Bool
$c<= :: forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType).
Manipulation with db params columns
-> Manipulation with db params columns -> Bool
< :: Manipulation with db params columns
-> Manipulation with db params columns -> Bool
$c< :: forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType).
Manipulation with db params columns
-> Manipulation with db params columns -> Bool
compare :: Manipulation with db params columns
-> Manipulation with db params columns -> Ordering
$ccompare :: forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType).
Manipulation with db params columns
-> Manipulation with db params columns -> Ordering
$cp1Ord :: forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType).
Eq (Manipulation with db params columns)
Ord)
deriving newtype (Manipulation with db params columns -> ()
(Manipulation with db params columns -> ())
-> NFData (Manipulation with db params columns)
forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType).
Manipulation with db params columns -> ()
forall a. (a -> ()) -> NFData a
rnf :: Manipulation with db params columns -> ()
$crnf :: forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType).
Manipulation with db params columns -> ()
NFData)
instance RenderSQL (Manipulation with db params columns) where
renderSQL :: Manipulation with db params columns -> ByteString
renderSQL = Manipulation with db params columns -> ByteString
forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType).
Manipulation with db params columns -> ByteString
renderManipulation
instance With Manipulation where
with :: Path (CommonTableExpression Manipulation db params) with0 with1
-> Manipulation with1 db params row
-> Manipulation with0 db params row
with Path (CommonTableExpression Manipulation db params) with0 with1
Done Manipulation with1 db params row
manip = Manipulation with0 db params row
Manipulation with1 db params row
manip
with Path (CommonTableExpression Manipulation db params) with0 with1
ctes Manipulation with1 db params row
manip = ByteString -> Manipulation with0 db params row
forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType).
ByteString -> Manipulation with db params columns
UnsafeManipulation (ByteString -> Manipulation with0 db params row)
-> ByteString -> Manipulation with0 db params row
forall a b. (a -> b) -> a -> b
$
ByteString
"WITH" ByteString -> ByteString -> ByteString
<+> [ByteString] -> ByteString
commaSeparated ((forall (x1 :: FromType) (y1 :: FromType).
CommonTableExpression Manipulation db params x1 y1 -> ByteString)
-> Path (CommonTableExpression Manipulation db params) with0 with1
-> [ByteString]
forall k (c :: (k -> k -> *) -> k -> k -> *) (p :: k -> k -> *) a
(x :: k) (y :: k).
QFoldable c =>
(forall (x1 :: k) (y1 :: k). p x1 y1 -> a) -> c p x y -> [a]
qtoList forall (x1 :: FromType) (y1 :: FromType).
CommonTableExpression Manipulation db params x1 y1 -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Path (CommonTableExpression Manipulation db params) with0 with1
ctes) ByteString -> ByteString -> ByteString
<+> Manipulation with1 db params row -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Manipulation with1 db params row
manip
type family Manipulation_ (db :: SchemasType) (params :: Type) (row :: Type) where
Manipulation_ db params row = Manipulation '[] db (TuplePG params) (RowPG row)
queryStatement
:: Query '[] with db params columns
-> Manipulation with db params columns
queryStatement :: Query '[] with db params columns
-> Manipulation with db params columns
queryStatement Query '[] with db params columns
q = ByteString -> Manipulation with db params columns
forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType).
ByteString -> Manipulation with db params columns
UnsafeManipulation (ByteString -> Manipulation with db params columns)
-> ByteString -> Manipulation with db params columns
forall a b. (a -> b) -> a -> b
$ Query '[] with db params columns -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Query '[] with db params columns
q
newtype ReturningClause with db params from row =
Returning (Selection 'Ungrouped '[] with db params from row)
instance RenderSQL (ReturningClause with db params from row) where
renderSQL :: ReturningClause with db params from row -> ByteString
renderSQL = \case
Returning (List NP (Aliased (Expression 'Ungrouped '[] with db params from)) row
Nil) -> ByteString
""
Returning Selection 'Ungrouped '[] with db params from row
selection -> ByteString
" RETURNING" ByteString -> ByteString -> ByteString
<+> Selection 'Ungrouped '[] with db params from row -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Selection 'Ungrouped '[] with db params from row
selection
pattern Returning_
:: SOP.SListI row
=> NP (Aliased (Expression 'Ungrouped '[] with db params from)) row
-> ReturningClause with db params from row
pattern $bReturning_ :: NP (Aliased (Expression 'Ungrouped '[] with db params from)) row
-> ReturningClause with db params from row
$mReturning_ :: forall r (row :: RowType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
SListI row =>
ReturningClause with db params from row
-> (NP
(Aliased (Expression 'Ungrouped '[] with db params from)) row
-> r)
-> (Void# -> r)
-> r
Returning_ list = Returning (List list)
data UsingClause with db params from where
NoUsing :: UsingClause with db params '[]
Using
:: FromClause '[] with db params from
-> UsingClause with db params from