| Copyright | (c) Eitan Chatav 2019 |
|---|---|
| Maintainer | eitan@morphism.tech |
| Stability | experimental |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Squeal.PostgreSQL.Manipulation.Insert
Description
insert statements
Synopsis
- insertInto :: (Has sch db schema, Has tab0 schema ('Table table), SListI (TableToColumns table), SListI row) => Aliased (QualifiedAlias sch) (tab ::: tab0) -> QueryClause with db params (TableToColumns table) -> ConflictClause tab with db params table -> ReturningClause with db params '[tab ::: TableToRow table] row -> Manipulation with db params row
- insertInto_ :: (Has sch db schema, Has tab0 schema ('Table table), SListI (TableToColumns table)) => Aliased (QualifiedAlias sch) (tab ::: tab0) -> QueryClause with db params (TableToColumns table) -> Manipulation with db params '[]
- data QueryClause with db params columns where
- Values :: SListI columns => NP (Aliased (Optional (Expression 'Ungrouped '[] with db params from))) columns -> [NP (Aliased (Optional (Expression 'Ungrouped '[] with db params from))) columns] -> QueryClause with db params columns
- Select :: SListI columns => NP (Aliased (Optional (Expression grp '[] with db params from))) columns -> TableExpression grp '[] with db params from -> QueryClause with db params columns
- Subquery :: ColumnsToRow columns ~ row => Query '[] with db params row -> QueryClause with db params columns
- pattern Values_ :: SListI columns => NP (Aliased (Optional (Expression 'Ungrouped '[] with db params from))) columns -> QueryClause with db params columns
- inlineValues :: (IsRecord hask xs, AllZip InlineColumn xs columns) => hask -> [hask] -> QueryClause with db params columns
- inlineValues_ :: (IsRecord hask xs, AllZip InlineColumn xs columns) => hask -> QueryClause with db params columns
- data ConflictClause tab with db params table where
- OnConflictDoRaise :: ConflictClause tab with db params table
- OnConflict :: ConflictTarget table -> ConflictAction tab with db params table -> ConflictClause tab with db params table
- data ConflictTarget table where
- OnConstraint :: Has con constraints constraint => Alias con -> ConflictTarget (constraints :=> columns)
- data ConflictAction tab with db params table where
- DoNothing :: ConflictAction tab with db params table
- DoUpdate :: (row ~ TableToRow table, from ~ '[tab ::: row, "excluded" ::: row], Updatable table updates) => NP (Aliased (Optional (Expression 'Ungrouped '[] with db params from))) updates -> [Condition 'Ungrouped '[] with db params from] -> ConflictAction tab with db params table
Insert
Arguments
| :: (Has sch db schema, Has tab0 schema ('Table table), SListI (TableToColumns table), SListI row) | |
| => Aliased (QualifiedAlias sch) (tab ::: tab0) | table |
| -> QueryClause with db params (TableToColumns table) | what to insert |
| -> ConflictClause tab with db params table | what to do in case of conflict |
| -> ReturningClause with db params '[tab ::: TableToRow table] row | what to return |
| -> Manipulation with db params row |
When a table is created, it contains no data. The first thing to do before a database can be of much use is to insert data. Data is conceptually inserted one row at a time. Of course you can also insert more than one row, but there is no way to insert less than one row. Even if you know only some column values, a complete row must be created.
>>>type CustomersColumns = '["name" ::: 'NoDef :=> 'NotNull 'PGtext, "email" ::: 'NoDef :=> 'NotNull 'PGtext]>>>type CustomersConstraints = '["uq" ::: 'Unique '["name"]]>>>type CustomersSchema = '["customers" ::: 'Table (CustomersConstraints :=> CustomersColumns)]>>>:{let manp :: Manipulation with (Public CustomersSchema) '[] '[] manp = 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 manp :} INSERT INTO "customers" AS "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"))
Arguments
| :: (Has sch db schema, Has tab0 schema ('Table table), SListI (TableToColumns table)) | |
| => Aliased (QualifiedAlias sch) (tab ::: tab0) | table |
| -> QueryClause with db params (TableToColumns table) | what to insert |
| -> Manipulation with db params '[] |
Like insertInto but with OnConflictDoRaise and no ReturningClause.
>>>type Columns = '["col1" ::: 'NoDef :=> 'Null 'PGint4, "col2" ::: 'Def :=> 'NotNull 'PGint4]>>>type Schema = '["tab" ::: 'Table ('[] :=> Columns)]>>>:{let manp :: Manipulation with (Public Schema) '[] '[] manp = insertInto_ #tab (Values_ (Set 2 `as` #col1 :* Default `as` #col2)) in printSQL manp :} INSERT INTO "tab" AS "tab" ("col1", "col2") VALUES ((2 :: int4), DEFAULT)
Clauses
data QueryClause with db params columns where Source #
A QueryClause describes what to insertInto a table.
Constructors
| Values | |
Fields
| |
| Select | |
Fields
| |
| Subquery | |
Fields
| |
Instances
| RenderSQL (QueryClause with db params columns) Source # | |
Defined in Squeal.PostgreSQL.Manipulation.Insert Methods renderSQL :: QueryClause with db params columns -> ByteString Source # | |
Arguments
| :: SListI columns | |
| => NP (Aliased (Optional (Expression 'Ungrouped '[] with db params from))) columns | row of values |
| -> QueryClause with db params columns |
Values_ describes a single NP list of Aliased Optional Expressions
whose ColumnsType must match the tables'.
Arguments
| :: (IsRecord hask xs, AllZip InlineColumn xs columns) | |
| => hask | record |
| -> [hask] | more |
| -> QueryClause with db params columns |
inlineValues Haskell records in insertInto.
Arguments
| :: (IsRecord hask xs, AllZip InlineColumn xs columns) | |
| => hask | record |
| -> QueryClause with db params columns |
inlineValues_ a Haskell record in insertInto.
data ConflictClause tab with db params table where Source #
A ConflictClause specifies an action to perform upon a constraint
violation. OnConflictDoRaise will raise an error.
OnConflict DoNothing simply avoids inserting a row.
OnConflict DoUpdate updates the existing row that conflicts with the row
proposed for insertion.
Constructors
| OnConflictDoRaise :: ConflictClause tab with db params table | |
| OnConflict | |
Fields
| |
Instances
| SListI (TableToColumns table) => RenderSQL (ConflictClause tab with db params table) Source # | Render a |
Defined in Squeal.PostgreSQL.Manipulation.Insert Methods renderSQL :: ConflictClause tab with db params table -> ByteString Source # | |
data ConflictTarget table where Source #
A ConflictTarget specifies the constraint violation that triggers a
ConflictAction.
Constructors
| OnConstraint :: Has con constraints constraint => Alias con -> ConflictTarget (constraints :=> columns) |
Instances
| RenderSQL (ConflictTarget constraints) Source # | Render a |
Defined in Squeal.PostgreSQL.Manipulation.Insert Methods renderSQL :: ConflictTarget constraints -> ByteString Source # | |
data ConflictAction tab with db params table where Source #
ConflictAction specifies an alternative OnConflict action.
It can be either DoNothing, or a DoUpdate clause specifying
the exact details of the update action to be performed in case of a conflict.
The Set and WHERE Conditions in OnConflict DoUpdate have access to the
existing row using the table's name, and to rows proposed
for insertion using the special #excluded row.
OnConflict DoNothing simply avoids inserting a row as its alternative action.
OnConflict DoUpdate updates the existing row that conflicts
with the row proposed for insertion as its alternative action.
Constructors
| DoNothing :: ConflictAction tab with db params table | |
| DoUpdate | |
Fields
| |
Instances
| RenderSQL (ConflictAction tab with db params table) Source # | |
Defined in Squeal.PostgreSQL.Manipulation.Insert Methods renderSQL :: ConflictAction tab with db params table -> ByteString Source # | |