Copyright | (c) Eitan Chatav 2017 |
---|---|
Maintainer | [email protected] |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Squeal.PostgreSQL.Manipulation
Description
Squeal data manipulation language.
- newtype Manipulation (schema :: TablesType) (params :: [NullityType]) (columns :: RelationType) = UnsafeManipulation {}
- queryStatement :: Query schema params columns -> Manipulation schema params columns
- data ColumnValue (columns :: RelationType) (params :: [NullityType]) (ty :: ColumnType) where
- Same :: ColumnValue (column ': columns) params ty
- Default :: ColumnValue columns params (Def :=> ty)
- Set :: (forall table. Expression '[table ::: columns] Ungrouped params ty) -> ColumnValue columns params (constraint :=> ty)
- data ReturningClause (columns :: ColumnsType) (params :: [NullityType]) (results :: RelationType) where
- ReturningStar :: results ~ ColumnsToRelation columns => ReturningClause columns params results
- Returning :: rel ~ ColumnsToRelation columns => NP (Aliased (Expression '[table ::: rel] Ungrouped params)) results -> ReturningClause columns params results
- data ConflictClause (columns :: ColumnsType) params where
- OnConflictDoRaise :: ConflictClause columns params
- OnConflictDoNothing :: ConflictClause columns params
- OnConflictDoUpdate :: NP (Aliased (ColumnValue (ColumnsToRelation columns) params)) columns -> [Condition '[table ::: ColumnsToRelation columns] Ungrouped params] -> ConflictClause columns params
- insertRows :: (SListI columns, SListI results, Has tab schema table, columns ~ TableToColumns table) => Alias tab -> NP (Aliased (ColumnValue '[] params)) columns -> [NP (Aliased (ColumnValue '[] params)) columns] -> ConflictClause columns params -> ReturningClause columns params results -> Manipulation schema params results
- insertRow :: (SListI columns, SListI results, Has tab schema table, columns ~ TableToColumns table) => Alias tab -> NP (Aliased (ColumnValue '[] params)) columns -> ConflictClause columns params -> ReturningClause columns params results -> Manipulation schema params results
- insertRows_ :: (SListI columns, Has tab schema table, columns ~ TableToColumns table) => Alias tab -> NP (Aliased (ColumnValue '[] params)) columns -> [NP (Aliased (ColumnValue '[] params)) columns] -> Manipulation schema params '[]
- insertRow_ :: (SListI columns, Has tab schema table, columns ~ TableToColumns table) => Alias tab -> NP (Aliased (ColumnValue '[] params)) columns -> Manipulation schema params '[]
- insertQuery :: (SListI columns, SListI results, Has tab schema table, columns ~ TableToColumns table) => Alias tab -> Query schema params (ColumnsToRelation columns) -> ConflictClause columns params -> ReturningClause columns params results -> Manipulation schema params results
- insertQuery_ :: (SListI columns, Has tab schema table, columns ~ TableToColumns table) => Alias tab -> Query schema params (ColumnsToRelation columns) -> Manipulation schema params '[]
- renderReturningClause :: SListI results => ReturningClause params columns results -> ByteString
- renderConflictClause :: SListI columns => ConflictClause columns params -> ByteString
- update :: (SListI columns, SListI results, Has tab schema table, columns ~ TableToColumns table) => Alias tab -> NP (Aliased (ColumnValue (ColumnsToRelation columns) params)) columns -> Condition '[tab ::: ColumnsToRelation columns] Ungrouped params -> ReturningClause columns params results -> Manipulation schema params results
- update_ :: (SListI columns, Has tab schema table, columns ~ TableToColumns table) => Alias tab -> NP (Aliased (ColumnValue (ColumnsToRelation columns) params)) columns -> Condition '[tab ::: ColumnsToRelation columns] Ungrouped params -> Manipulation schema params '[]
- deleteFrom :: (SListI results, Has tab schema table, columns ~ TableToColumns table) => Alias tab -> Condition '[tab ::: ColumnsToRelation columns] Ungrouped params -> ReturningClause columns params results -> Manipulation schema params results
- deleteFrom_ :: (Has tab schema table, columns ~ TableToColumns table) => Alias tab -> Condition '[tab ::: ColumnsToRelation columns] Ungrouped params -> Manipulation schema params '[]
- with :: SListI commons => NP (Aliased (Manipulation schema params)) commons -> Manipulation (Join (RelationsToTables commons) schema) params results -> Manipulation schema params results
Manipulation
newtype Manipulation (schema :: TablesType) (params :: [NullityType]) (columns :: RelationType) Source #
A Manipulation
is a statement which may modify data in the database,
but does not alter the schema. Examples are inserts, updates and deletes.
A Query
is also considered a Manipulation
even though it does not modify data.
simple insert:
>>>
:{
let manipulation :: Manipulation '[ "tab" ::: '[] :=> '[ "col1" ::: 'NoDef :=> 'NotNull 'PGint4 , "col2" ::: 'Def :=> 'NotNull 'PGint4 ]] '[] '[] manipulation = insertRow_ #tab (Set 2 `As` #col1 :* Default `As` #col2 :* Nil) in renderManipulation manipulation :} "INSERT INTO tab (col1, col2) VALUES (2, DEFAULT);"
parameterized insert:
>>>
:{
let manipulation :: Manipulation '[ "tab" ::: '[] :=> '[ "col1" ::: 'NoDef :=> 'NotNull 'PGint4 , "col2" ::: 'NoDef :=> 'NotNull 'PGint4 ]] '[ 'NotNull 'PGint4, 'NotNull 'PGint4 ] '[] manipulation = insertRow_ #tab (Set (param @1) `As` #col1 :* Set (param @2) `As` #col2 :* Nil) in renderManipulation manipulation :} "INSERT INTO tab (col1, col2) VALUES (($1 :: int4), ($2 :: int4));"
returning insert:
>>>
:{
let manipulation :: Manipulation '[ "tab" ::: '[] :=> '[ "col1" ::: 'NoDef :=> 'NotNull 'PGint4 , "col2" ::: 'Def :=> 'NotNull 'PGint4 ]] '[] '["fromOnly" ::: 'NotNull 'PGint4] manipulation = insertRow #tab (Set 2 `As` #col1 :* Default `As` #col2 :* Nil) OnConflictDoRaise (Returning (#col1 `As` #fromOnly :* Nil)) in renderManipulation manipulation :} "INSERT INTO tab (col1, col2) VALUES (2, DEFAULT) RETURNING col1 AS fromOnly;"
upsert:
>>>
:{
let manipulation :: Manipulation '[ "tab" ::: '[] :=> '[ "col1" ::: 'NoDef :=> 'NotNull 'PGint4 , "col2" ::: 'NoDef :=> 'NotNull 'PGint4 ]] '[] '[ "sum" ::: 'NotNull 'PGint4] manipulation = insertRows #tab (Set 2 `As` #col1 :* Set 4 `As` #col2 :* Nil) [Set 6 `As` #col1 :* Set 8 `As` #col2 :* Nil] (OnConflictDoUpdate (Set 2 `As` #col1 :* Same `As` #col2 :* Nil) [#col1 .== #col2]) (Returning $ (#col1 + #col2) `As` #sum :* Nil) in renderManipulation manipulation :} "INSERT INTO tab (col1, col2) VALUES (2, 4), (6, 8) ON CONFLICT DO UPDATE SET col1 = 2 WHERE (col1 = col2) RETURNING (col1 + col2) AS sum;"
query insert:
>>>
:{
let manipulation :: Manipulation '[ "tab" ::: '[] :=> '[ "col1" ::: 'NoDef :=> 'NotNull 'PGint4 , "col2" ::: 'NoDef :=> 'NotNull 'PGint4 ] , "other_tab" ::: '[] :=> '[ "col1" ::: 'NoDef :=> 'NotNull 'PGint4 , "col2" ::: 'NoDef :=> 'NotNull 'PGint4 ] ] '[] '[] manipulation = insertQuery_ #tab (selectStar (from (table (#other_tab `As` #t)))) in renderManipulation manipulation :} "INSERT INTO tab SELECT * FROM other_tab AS t;"
update:
>>>
:{
let manipulation :: Manipulation '[ "tab" ::: '[] :=> '[ "col1" ::: 'NoDef :=> 'NotNull 'PGint4 , "col2" ::: 'NoDef :=> 'NotNull 'PGint4 ]] '[] '[] manipulation = update_ #tab (Set 2 `As` #col1 :* Same `As` #col2 :* Nil) (#col1 ./= #col2) in renderManipulation manipulation :} "UPDATE tab SET col1 = 2 WHERE (col1 <> col2);"
delete:
>>>
:{
let manipulation :: Manipulation '[ "tab" ::: '[] :=> '[ "col1" ::: 'NoDef :=> 'NotNull 'PGint4 , "col2" ::: 'NoDef :=> 'NotNull 'PGint4 ]] '[] '[ "col1" ::: 'NotNull 'PGint4 , "col2" ::: 'NotNull 'PGint4 ] manipulation = deleteFrom #tab (#col1 .== #col2) ReturningStar in renderManipulation manipulation :} "DELETE FROM tab WHERE (col1 = col2) RETURNING *;"
Constructors
UnsafeManipulation | |
Fields |
Instances
Eq (Manipulation schema params columns) Source # | |
Ord (Manipulation schema params columns) Source # | |
Show (Manipulation schema params columns) Source # | |
Generic (Manipulation schema params columns) Source # | |
NFData (Manipulation schema params columns) Source # | |
type Rep (Manipulation schema params columns) Source # | |
queryStatement :: Query schema params columns -> Manipulation schema params columns Source #
Convert a Query
into a Manipulation
.
data ColumnValue (columns :: RelationType) (params :: [NullityType]) (ty :: ColumnType) where Source #
ColumnValue
s are values to insert or update in a row
Same
updates with the same value.
Default
inserts or updates with the DEFAULT
value
Set
a value to be an Expression
, relative to the given
row for an update, and closed for an insert.
Constructors
Same :: ColumnValue (column ': columns) params ty | |
Default :: ColumnValue columns params (Def :=> ty) | |
Set :: (forall table. Expression '[table ::: columns] Ungrouped params ty) -> ColumnValue columns params (constraint :=> ty) |
data ReturningClause (columns :: ColumnsType) (params :: [NullityType]) (results :: RelationType) where 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 OnConflictDoUpdate
condition was not satisfied,
the row will not be returned. ReturningStar
will return all columns
in the row. Use Returning Nil
in the common case where no return
values are desired.
Constructors
ReturningStar :: results ~ ColumnsToRelation columns => ReturningClause columns params results | |
Returning :: rel ~ ColumnsToRelation columns => NP (Aliased (Expression '[table ::: rel] Ungrouped params)) results -> ReturningClause columns params results |
data ConflictClause (columns :: ColumnsType) params where Source #
A ConflictClause
specifies an action to perform upon a constraint
violation. OnConflictDoRaise
will raise an error.
OnConflictDoNothing
simply avoids inserting a row.
OnConflictDoUpdate
updates the existing row that conflicts with the row
proposed for insertion.
Constructors
OnConflictDoRaise :: ConflictClause columns params | |
OnConflictDoNothing :: ConflictClause columns params | |
OnConflictDoUpdate :: NP (Aliased (ColumnValue (ColumnsToRelation columns) params)) columns -> [Condition '[table ::: ColumnsToRelation columns] Ungrouped params] -> ConflictClause columns params |
Insert
Arguments
:: (SListI columns, SListI results, Has tab schema table, columns ~ TableToColumns table) | |
=> Alias tab | table to insert into |
-> NP (Aliased (ColumnValue '[] params)) columns | row to insert |
-> [NP (Aliased (ColumnValue '[] params)) columns] | more rows to insert |
-> ConflictClause columns params | what to do in case of constraint conflict |
-> ReturningClause columns params results | results to return |
-> Manipulation schema params results |
Insert multiple rows.
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.
Arguments
:: (SListI columns, SListI results, Has tab schema table, columns ~ TableToColumns table) | |
=> Alias tab | table to insert into |
-> NP (Aliased (ColumnValue '[] params)) columns | row to insert |
-> ConflictClause columns params | what to do in case of constraint conflict |
-> ReturningClause columns params results | results to return |
-> Manipulation schema params results |
Insert a single row.
Arguments
:: (SListI columns, Has tab schema table, columns ~ TableToColumns table) | |
=> Alias tab | table to insert into |
-> NP (Aliased (ColumnValue '[] params)) columns | row to insert |
-> [NP (Aliased (ColumnValue '[] params)) columns] | more rows to insert |
-> Manipulation schema params '[] |
Insert multiple rows returning Nil
and raising an error on conflicts.
Arguments
:: (SListI columns, Has tab schema table, columns ~ TableToColumns table) | |
=> Alias tab | table to insert into |
-> NP (Aliased (ColumnValue '[] params)) columns | row to insert |
-> Manipulation schema params '[] |
Insert a single row returning Nil
and raising an error on conflicts.
Arguments
:: (SListI columns, SListI results, Has tab schema table, columns ~ TableToColumns table) | |
=> Alias tab | table to insert into |
-> Query schema params (ColumnsToRelation columns) | |
-> ConflictClause columns params | what to do in case of constraint conflict |
-> ReturningClause columns params results | results to return |
-> Manipulation schema params results |
Insert a Query
.
Arguments
:: (SListI columns, Has tab schema table, columns ~ TableToColumns table) | |
=> Alias tab | table to insert into |
-> Query schema params (ColumnsToRelation columns) | |
-> Manipulation schema params '[] |
renderReturningClause :: SListI results => ReturningClause params columns results -> ByteString Source #
Render a ReturningClause
.
renderConflictClause :: SListI columns => ConflictClause columns params -> ByteString Source #
Render a ConflictClause
.
Update
Arguments
:: (SListI columns, SListI results, Has tab schema table, columns ~ TableToColumns table) | |
=> Alias tab | table to update |
-> NP (Aliased (ColumnValue (ColumnsToRelation columns) params)) columns | modified values to replace old values |
-> Condition '[tab ::: ColumnsToRelation columns] Ungrouped params | condition under which to perform update on a row |
-> ReturningClause columns params results | results to return |
-> Manipulation schema params results |
An update
command changes the values of the specified columns
in all rows that satisfy the condition.
Arguments
:: (SListI columns, Has tab schema table, columns ~ TableToColumns table) | |
=> Alias tab | table to update |
-> NP (Aliased (ColumnValue (ColumnsToRelation columns) params)) columns | modified values to replace old values |
-> Condition '[tab ::: ColumnsToRelation columns] Ungrouped params | condition under which to perform update on a row |
-> Manipulation schema params '[] |
Update a row returning Nil
.
Delete
Arguments
:: (SListI results, Has tab schema table, columns ~ TableToColumns table) | |
=> Alias tab | table to delete from |
-> Condition '[tab ::: ColumnsToRelation columns] Ungrouped params | condition under which to delete a row |
-> ReturningClause columns params results | results to return |
-> Manipulation schema params results |
Delete rows of a table.
Arguments
:: (Has tab schema table, columns ~ TableToColumns table) | |
=> Alias tab | table to delete from |
-> Condition '[tab ::: ColumnsToRelation columns] Ungrouped params | condition under which to delete a row |
-> Manipulation schema params '[] |
Delete rows returning Nil
.
With
Arguments
:: SListI commons | |
=> NP (Aliased (Manipulation schema params)) commons | common table expressions |
-> Manipulation (Join (RelationsToTables commons) schema) params results | |
-> Manipulation schema params results |
with
provides a way to write auxiliary statements for use in a larger statement.
These statements, which are often referred to as Common Table Expressions or CTEs,
can be thought of as defining temporary tables that exist just for one statement.
>>>
type ProductsTable = '[] :=> '["product" ::: 'NoDef :=> 'NotNull 'PGtext, "date" ::: 'Def :=> 'NotNull 'PGdate]
>>>
:{
let manipulation :: Manipulation '["products" ::: ProductsTable, "products_deleted" ::: ProductsTable] '[ 'NotNull 'PGdate] '[] manipulation = with (deleteFrom #products (#date .< param @1) ReturningStar `As` #deleted_rows :* Nil) (insertQuery_ #products_deleted (selectStar (from (table (#deleted_rows `As` #t))))) in renderManipulation manipulation :} "WITH deleted_rows AS (DELETE FROM products WHERE (date < ($1 :: date)) RETURNING *) INSERT INTO products_deleted SELECT * FROM deleted_rows AS t;"