{-# 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 pro x = UnsafeManipulation $
"CALL" <+> pro <> parenthesized (renderSQL 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 = unsafeCall . renderSQL
unsafeCallN
:: SListI xs
=> ByteString
-> NP (Expression 'Ungrouped '[] with db params '[]) xs
-> Manipulation with db params '[]
unsafeCallN pro xs = UnsafeManipulation $
"CALL" <+> pro <> parenthesized (renderCommaSeparated renderSQL 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 = unsafeCallN . renderSQL