{-# LANGUAGE
DeriveGeneric
, DerivingStrategies
, FlexibleContexts
, FlexibleInstances
, GADTs
, GeneralizedNewtypeDeriving
, LambdaCase
, MultiParamTypeClasses
, OverloadedStrings
, PatternSynonyms
, QuantifiedConstraints
, RankNTypes
, ScopedTypeVariables
, TypeApplications
, TypeFamilies
, TypeInType
, TypeOperators
, UndecidableInstances
#-}
module Squeal.PostgreSQL.Manipulation.Call
(
call
, unsafeCall
, callN
, unsafeCallN
) where
import Data.ByteString hiding (foldr)
import Generics.SOP (SListI)
import Squeal.PostgreSQL.Type.Alias
import Squeal.PostgreSQL.Expression
import Squeal.PostgreSQL.Manipulation
import Squeal.PostgreSQL.Type.List
import Squeal.PostgreSQL.Render
import Squeal.PostgreSQL.Type.Schema
unsafeCall
:: ByteString
-> Expression 'Ungrouped '[] with db params '[] x
-> Manipulation with db params '[]
unsafeCall :: ByteString
-> Expression 'Ungrouped '[] with db params '[] x
-> Manipulation with db params '[]
unsafeCall ByteString
pro Expression 'Ungrouped '[] with db params '[] x
x = ByteString -> Manipulation with db params '[]
forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType).
ByteString -> Manipulation with db params columns
UnsafeManipulation (ByteString -> Manipulation with db params '[])
-> ByteString -> Manipulation with db params '[]
forall a b. (a -> b) -> a -> b
$
ByteString
"CALL" ByteString -> ByteString -> ByteString
<+> ByteString
pro ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString -> ByteString
parenthesized (Expression 'Ungrouped '[] with db params '[] x -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Expression 'Ungrouped '[] with db params '[] x
x)
call
:: ( Has sch db schema
, Has pro schema ('Procedure '[x]) )
=> QualifiedAlias sch pro
-> Expression 'Ungrouped '[] with db params '[] x
-> Manipulation with db params '[]
call :: QualifiedAlias sch pro
-> Expression 'Ungrouped '[] with db params '[] x
-> Manipulation with db params '[]
call = ByteString
-> Expression 'Ungrouped '[] with db params '[] x
-> Manipulation with db params '[]
forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (x :: NullType).
ByteString
-> Expression 'Ungrouped '[] with db params '[] x
-> Manipulation with db params '[]
unsafeCall (ByteString
-> Expression 'Ungrouped '[] with db params '[] x
-> Manipulation with db params '[])
-> (QualifiedAlias sch pro -> ByteString)
-> QualifiedAlias sch pro
-> Expression 'Ungrouped '[] with db params '[] x
-> Manipulation with db params '[]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QualifiedAlias sch pro -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL
unsafeCallN
:: SListI xs
=> ByteString
-> NP (Expression 'Ungrouped '[] with db params '[]) xs
-> Manipulation with db params '[]
unsafeCallN :: ByteString
-> NP (Expression 'Ungrouped '[] with db params '[]) xs
-> Manipulation with db params '[]
unsafeCallN ByteString
pro NP (Expression 'Ungrouped '[] with db params '[]) xs
xs = ByteString -> Manipulation with db params '[]
forall (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (columns :: RowType).
ByteString -> Manipulation with db params columns
UnsafeManipulation (ByteString -> Manipulation with db params '[])
-> ByteString -> Manipulation with db params '[]
forall a b. (a -> b) -> a -> b
$
ByteString
"CALL" ByteString -> ByteString -> ByteString
<+> ByteString
pro ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString -> ByteString
parenthesized ((forall (x :: NullType).
Expression 'Ungrouped '[] with db params '[] x -> ByteString)
-> NP (Expression 'Ungrouped '[] with db params '[]) xs
-> ByteString
forall k (xs :: [k]) (expression :: k -> *).
SListI xs =>
(forall (x :: k). expression x -> ByteString)
-> NP expression xs -> ByteString
renderCommaSeparated forall sql. RenderSQL sql => sql -> ByteString
forall (x :: NullType).
Expression 'Ungrouped '[] with db params '[] x -> ByteString
renderSQL NP (Expression 'Ungrouped '[] with db params '[]) xs
xs)
callN
:: ( Has sch db schema
, Has pro schema ('Procedure xs)
, SListI xs )
=> QualifiedAlias sch pro
-> NP (Expression 'Ungrouped '[] with db params '[]) xs
-> Manipulation with db params '[]
callN :: QualifiedAlias sch pro
-> NP (Expression 'Ungrouped '[] with db params '[]) xs
-> Manipulation with db params '[]
callN = ByteString
-> NP (Expression 'Ungrouped '[] with db params '[]) xs
-> Manipulation with db params '[]
forall (xs :: [NullType]) (with :: FromType) (db :: SchemasType)
(params :: [NullType]).
SListI xs =>
ByteString
-> NP (Expression 'Ungrouped '[] with db params '[]) xs
-> Manipulation with db params '[]
unsafeCallN (ByteString
-> NP (Expression 'Ungrouped '[] with db params '[]) xs
-> Manipulation with db params '[])
-> (QualifiedAlias sch pro -> ByteString)
-> QualifiedAlias sch pro
-> NP (Expression 'Ungrouped '[] with db params '[]) xs
-> Manipulation with db params '[]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QualifiedAlias sch pro -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL