squeal-postgresql-0.9.1.3: Squeal PostgreSQL Library
Copyright(c) Eitan Chatav 2019
Maintainereitan@morphism.tech
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

Squeal.PostgreSQL.Manipulation.Insert

Description

insert statements

Synopsis

Insert

insertInto Source #

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"))

insertInto_ Source #

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

Instances details
RenderSQL (QueryClause with db params columns) Source # 
Instance details

Defined in Squeal.PostgreSQL.Manipulation.Insert

Methods

renderSQL :: QueryClause with db params columns -> ByteString Source #

pattern Values_ 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'.

inlineValues Source #

Arguments

:: (IsRecord hask xs, AllZip InlineColumn xs columns) 
=> hask

record

-> [hask]

more

-> QueryClause with db params columns 

inlineValues Haskell records in insertInto.

inlineValues_ Source #

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

Instances details
SListI (TableToColumns table) => RenderSQL (ConflictClause tab with db params table) Source #

Render a ConflictClause.

Instance details

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

Instances details
RenderSQL (ConflictTarget constraints) Source #

Render a ConflictTarget

Instance details

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

Instances details
RenderSQL (ConflictAction tab with db params table) Source # 
Instance details

Defined in Squeal.PostgreSQL.Manipulation.Insert

Methods

renderSQL :: ConflictAction tab with db params table -> ByteString Source #