| Copyright | (c) Eitan Chatav 2019 |
|---|---|
| Maintainer | eitan@morphism.tech |
| Stability | experimental |
| Safe Haskell | None |
| Language | Haskell2010 |
Squeal.PostgreSQL.Manipulation
Contents
Description
data manipulation language
Synopsis
- type family Manipulation_ (db :: SchemasType) (params :: Type) (row :: Type) where ...
- newtype Manipulation (with :: FromType) (db :: SchemasType) (params :: [NullType]) (columns :: RowType) = UnsafeManipulation {}
- queryStatement :: Query '[] with db params columns -> Manipulation with db params columns
- newtype ReturningClause with db params from row = Returning (Selection Ungrouped '[] with db params from row)
- pattern Returning_ :: SListI row => NP (Aliased (Expression Ungrouped '[] with db params from)) row -> ReturningClause with db params from row
Manipulation
type family Manipulation_ (db :: SchemasType) (params :: Type) (row :: Type) where ... Source #
The top level Manipulation_ type is parameterized by a db SchemasType,
against which the query is type-checked, an input params Haskell Type,
and an ouput row Haskell Type.
Manipulation_ is a type family which resolves into a Manipulation,
so don't be fooled by the input params and output row Haskell Types,
which are converted into appropriate
Postgres [NullType] params and RowType rows.
Use a top-level Statement to
fix actual Haskell input params and output rows.
A top-level Manipulation_ can be run
using manipulateParams, or if params = ()
using manipulate.
Generally, params will be a Haskell tuple or record whose entries
may be referenced using positional
params and row will be a
Haskell record, whose entries will be targeted using overloaded labels.
>>>:set -XDeriveAnyClass -XDerivingStrategies>>>:{data Row a b = Row { col1 :: a, col2 :: b } deriving stock (GHC.Generic) deriving anyclass (SOP.Generic, SOP.HasDatatypeInfo) :}
simple insert:
>>>type Columns = '["col1" ::: 'NoDef :=> 'Null 'PGint4, "col2" ::: 'Def :=> 'NotNull 'PGint4]>>>type Schema = '["tab" ::: 'Table ('[] :=> Columns)]>>>:{let manipulation :: Manipulation_ (Public Schema) () () manipulation = insertInto_ #tab (Values_ (Set 2 `as` #col1 :* Default `as` #col2)) in printSQL manipulation :} INSERT INTO "tab" ("col1", "col2") VALUES ((2 :: int4), DEFAULT)
out-of-line parameterized insert:
>>>type Columns = '["col1" ::: 'Def :=> 'NotNull 'PGint4, "col2" ::: 'NoDef :=> 'NotNull 'PGint4]>>>type Schema = '["tab" ::: 'Table ('[] :=> Columns)]>>>:{let manipulation :: Manipulation_ (Public Schema) (Only Int32) () manipulation = insertInto_ #tab $ Values_ (Default `as` #col1 :* Set (param @1) `as` #col2) in printSQL manipulation :} INSERT INTO "tab" ("col1", "col2") VALUES (DEFAULT, ($1 :: int4))
in-line parameterized insert:
>>>type Columns = '["col1" ::: 'Def :=> 'NotNull 'PGint4, "col2" ::: 'NoDef :=> 'NotNull 'PGint4]>>>type Schema = '["tab" ::: 'Table ('[] :=> Columns)]>>>:{let manipulation :: Manipulation_ (Public Schema) () () manipulation = insertInto_ #tab $ inlineValues (Row {col1 = Default , col2 = 2 :: Int32}) [Row {col1 = NotDefault (3 :: Int32), col2 = 4 :: Int32}] in printSQL manipulation :} INSERT INTO "tab" ("col1", "col2") VALUES (DEFAULT, (2 :: int4)), ((3 :: int4), (4 :: int4))
returning insert:
>>>:{let manipulation :: Manipulation_ (Public Schema) () (Only Int32) manipulation = insertInto #tab (Values_ (Set 2 `as` #col1 :* Set 3 `as` #col2)) OnConflictDoRaise (Returning (#col1 `as` #fromOnly)) in printSQL manipulation :} INSERT INTO "tab" ("col1", "col2") VALUES ((2 :: int4), (3 :: int4)) RETURNING "col1" AS "fromOnly"
upsert:
>>>type CustomersColumns = '["name" ::: 'NoDef :=> 'NotNull 'PGtext, "email" ::: 'NoDef :=> 'NotNull 'PGtext]>>>type CustomersConstraints = '["uq" ::: 'Unique '["name"]]>>>type CustomersSchema = '["customers" ::: 'Table (CustomersConstraints :=> CustomersColumns)]>>>:{let manipulation :: Manipulation_ (Public CustomersSchema) () () manipulation = insertInto #customers (Values_ (Set "John Smith" `as` #name :* Set "john@smith.com" `as` #email)) (OnConflict (OnConstraint #uq) (DoUpdate (Set (#excluded ! #email <> "; " <> #customers ! #email) `as` #email) [])) (Returning_ Nil) in printSQL manipulation :} INSERT INTO "customers" ("name", "email") VALUES ((E'John Smith' :: text), (E'john@smith.com' :: text)) ON CONFLICT ON CONSTRAINT "uq" DO UPDATE SET "email" = ("excluded"."email" || ((E'; ' :: text) || "customers"."email"))
query insert:
>>>:{let manipulation :: Manipulation_ (Public Schema) () () manipulation = insertInto_ #tab (Subquery (select Star (from (table #tab)))) in printSQL manipulation :} INSERT INTO "tab" SELECT * FROM "tab" AS "tab"
update:
>>>:{let manipulation :: Manipulation_ (Public Schema) () () manipulation = update_ #tab (Set 2 `as` #col1) (#col1 ./= #col2) in printSQL manipulation :} UPDATE "tab" SET "col1" = (2 :: int4) WHERE ("col1" <> "col2")
delete:
>>>:{let manipulation :: Manipulation_ (Public Schema) () (Row Int32 Int32) manipulation = deleteFrom #tab NoUsing (#col1 .== #col2) (Returning Star) in printSQL manipulation :} DELETE FROM "tab" WHERE ("col1" = "col2") RETURNING *
delete and using clause:
>>>:{type Schema3 = '[ "tab" ::: 'Table ('[] :=> Columns) , "other_tab" ::: 'Table ('[] :=> Columns) , "third_tab" ::: 'Table ('[] :=> Columns) ] :}
>>>:{let manipulation :: Manipulation_ (Public Schema3) () () manipulation = deleteFrom #tab (Using (table #other_tab & also (table #third_tab))) ( (#tab ! #col2 .== #other_tab ! #col2) .&& (#tab ! #col2 .== #third_tab ! #col2) ) (Returning_ Nil) in printSQL manipulation :} DELETE FROM "tab" USING "other_tab" AS "other_tab", "third_tab" AS "third_tab" WHERE (("tab"."col2" = "other_tab"."col2") AND ("tab"."col2" = "third_tab"."col2"))
with manipulation:
>>>type ProductsColumns = '["product" ::: 'NoDef :=> 'NotNull 'PGtext, "date" ::: 'Def :=> 'NotNull 'PGdate]>>>type ProductsSchema = '["products" ::: 'Table ('[] :=> ProductsColumns), "products_deleted" ::: 'Table ('[] :=> ProductsColumns)]>>>:{let manipulation :: Manipulation_ (Public ProductsSchema) (Only Day) () manipulation = with (deleteFrom #products NoUsing (#date .< param @1) (Returning Star) `as` #del) (insertInto_ #products_deleted (Subquery (select Star (from (common #del))))) in printSQL manipulation :} WITH "del" AS (DELETE FROM "products" WHERE ("date" < ($1 :: date)) RETURNING *) INSERT INTO "products_deleted" SELECT * FROM "del" AS "del"
Equations
| Manipulation_ db params row = Manipulation '[] db (TuplePG params) (RowPG row) |
newtype Manipulation (with :: FromType) (db :: SchemasType) (params :: [NullType]) (columns :: RowType) Source #
A Manipulation is a statement which may modify data in the database,
but does not alter its schemas. Examples are inserts, updates and deletes.
A Query is also considered a Manipulation even though it does not modify data.
The general Manipulation type is parameterized by
Constructors
| UnsafeManipulation | |
Fields | |
Instances
| With Manipulation Source # | |
Defined in Squeal.PostgreSQL.Manipulation Methods with :: Path (CommonTableExpression Manipulation db params) with0 with1 -> Manipulation with1 db params row -> Manipulation with0 db params row Source # | |
| Eq (Manipulation with db params columns) Source # | |
Defined in Squeal.PostgreSQL.Manipulation Methods (==) :: Manipulation with db params columns -> Manipulation with db params columns -> Bool # (/=) :: Manipulation with db params columns -> Manipulation with db params columns -> Bool # | |
| Ord (Manipulation with db params columns) Source # | |
Defined in Squeal.PostgreSQL.Manipulation Methods compare :: 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 # max :: Manipulation with db params columns -> Manipulation with db params columns -> Manipulation with db params columns # min :: Manipulation with db params columns -> Manipulation with db params columns -> Manipulation with db params columns # | |
| Show (Manipulation with db params columns) Source # | |
Defined in Squeal.PostgreSQL.Manipulation Methods showsPrec :: Int -> Manipulation with db params columns -> ShowS # show :: Manipulation with db params columns -> String # showList :: [Manipulation with db params columns] -> ShowS # | |
| Generic (Manipulation with db params columns) Source # | |
Defined in Squeal.PostgreSQL.Manipulation Associated Types type Rep (Manipulation with db params columns) :: Type -> Type # Methods from :: Manipulation with db params columns -> Rep (Manipulation with db params columns) x # to :: Rep (Manipulation with db params columns) x -> Manipulation with db params columns # | |
| NFData (Manipulation with db params columns) Source # | |
Defined in Squeal.PostgreSQL.Manipulation Methods rnf :: Manipulation with db params columns -> () # | |
| RenderSQL (Manipulation with db params columns) Source # | |
Defined in Squeal.PostgreSQL.Manipulation Methods renderSQL :: Manipulation with db params columns -> ByteString Source # | |
| type Rep (Manipulation with db params columns) Source # | |
Defined in Squeal.PostgreSQL.Manipulation type Rep (Manipulation with db params columns) = D1 (MetaData "Manipulation" "Squeal.PostgreSQL.Manipulation" "squeal-postgresql-0.6.0.2-55PJjSRSXxzaZJfRqaJ60" True) (C1 (MetaCons "UnsafeManipulation" PrefixI True) (S1 (MetaSel (Just "renderManipulation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString))) | |
Arguments
| :: Query '[] with db params columns |
|
| -> Manipulation with db params columns |
Convert a Query into a Manipulation.
newtype ReturningClause with db params from row Source #
A ReturningClause computes and return value(s) based
on each row actually inserted, updated or deleted. This is primarily
useful for obtaining values that were supplied by defaults, such as a
serial sequence number. However, any expression using the table's columns
is allowed. Only rows that were successfully inserted or updated or
deleted will be returned. For example, if a row was locked
but not updated because an OnConflict
DoUpdate condition was not satisfied,
the row will not be returned. Returning Star will return all columns
in the row. Use Returning Nil in the common case where no return
values are desired.
Instances
| RenderSQL (ReturningClause with db params from row) Source # | |
Defined in Squeal.PostgreSQL.Manipulation Methods renderSQL :: ReturningClause with db params from row -> ByteString Source # | |
pattern Returning_ Source #
Arguments
| :: SListI row | |
| => NP (Aliased (Expression Ungrouped '[] with db params from)) row | row of values |
| -> ReturningClause with db params from row |