Copyright | (c) Eitan Chatav 2017 |
---|---|
Maintainer | eitan@morphism.tech |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Squeal data manipulation language.
Synopsis
- type family Manipulation_ (schemas :: SchemasType) (params :: Type) (row :: Type) where ...
- newtype Manipulation (commons :: FromType) (schemas :: SchemasType) (params :: [NullityType]) (columns :: RowType) = UnsafeManipulation {}
- queryStatement :: Query '[] commons schemas params columns -> Manipulation commons schemas params columns
- insertInto :: (Has sch schemas schema, Has tab schema (Table table), columns ~ TableToColumns table, row0 ~ TableToRow table, SListI columns, SListI row1) => QualifiedAlias sch tab -> QueryClause commons schemas params columns -> ConflictClause tab commons schemas params table -> ReturningClause commons schemas params '[tab ::: row0] row1 -> Manipulation commons schemas params row1
- insertInto_ :: (Has sch schemas schema, Has tab schema (Table table), columns ~ TableToColumns table, row ~ TableToRow table, SListI columns) => QualifiedAlias sch tab -> QueryClause commons schemas params columns -> Manipulation commons schemas params '[]
- update :: (SListI columns, SListI row1, db ~ (commons :=> schemas), Has sch schemas schema, Has tab schema (Table table), row0 ~ TableToRow table, columns ~ TableToColumns table, All (HasIn columns) subcolumns, AllUnique subcolumns) => QualifiedAlias sch tab -> NP (Aliased (Optional (Expression '[] '[] Ungrouped schemas params '[tab ::: row0]))) subcolumns -> Condition '[] commons Ungrouped schemas params '[tab ::: row0] -> ReturningClause commons schemas params '[tab ::: row0] row1 -> Manipulation commons schemas params row1
- update_ :: (SListI columns, db ~ (commons :=> schemas), Has sch schemas schema, Has tab schema (Table table), row ~ TableToRow table, columns ~ TableToColumns table, All (HasIn columns) subcolumns, AllUnique subcolumns) => QualifiedAlias sch tab -> NP (Aliased (Optional (Expression '[] '[] Ungrouped schemas params '[tab ::: row]))) subcolumns -> Condition '[] commons Ungrouped schemas params '[tab ::: row] -> Manipulation commons schemas params '[]
- deleteFrom :: (SListI row1, db ~ (commons :=> schemas), Has sch schemas schema, Has tab schema (Table table), row0 ~ TableToRow table, columns ~ TableToColumns table) => QualifiedAlias sch tab -> UsingClause commons schemas params from -> Condition '[] commons Ungrouped schemas params ((tab ::: row0) ': from) -> ReturningClause commons schemas params '[tab ::: row0] row1 -> Manipulation commons schemas params row1
- deleteFrom_ :: (db ~ (commons :=> schemas), Has sch schemas schema, Has tab schema (Table table), row ~ TableToRow table, columns ~ TableToColumns table) => QualifiedAlias sch tab -> Condition '[] commons Ungrouped schemas params '[tab ::: row] -> Manipulation commons schemas params '[]
- data Optional expr ty where
- data QueryClause commons schemas params columns where
- Values :: SListI columns => NP (Aliased (Optional (Expression '[] commons Ungrouped schemas params '[]))) columns -> [NP (Aliased (Optional (Expression '[] commons Ungrouped schemas params '[]))) columns] -> QueryClause commons schemas params columns
- Select :: SListI columns => NP (Aliased (Optional (Expression '[] commons grp schemas params from))) columns -> TableExpression '[] commons grp schemas params from -> QueryClause commons schemas params columns
- Subquery :: ColumnsToRow columns ~ row => Query '[] commons schemas params row -> QueryClause commons schemas params columns
- pattern Values_ :: SListI columns => NP (Aliased (Optional (Expression '[] commons Ungrouped schemas params '[]))) columns -> QueryClause commons schemas params columns
- newtype ReturningClause commons schemas params from row = Returning (Selection '[] commons Ungrouped schemas params from row)
- pattern Returning_ :: SListI row => NP (Aliased (Expression '[] commons Ungrouped schemas params from)) row -> ReturningClause commons schemas params from row
- data ConflictClause tab commons schemas params table where
- OnConflictDoRaise :: ConflictClause tab commons schemas params table
- OnConflict :: ConflictTarget constraints -> ConflictAction tab commons schemas params columns -> ConflictClause tab commons schemas params (constraints :=> columns)
- data ConflictTarget constraints where
- OnConstraint :: Has con constraints constraint => Alias con -> ConflictTarget constraints
- data ConflictAction tab commons schemas params columns where
- DoNothing :: ConflictAction tab commons schemas params columns
- DoUpdate :: (row ~ ColumnsToRow columns, SListI columns, columns ~ (col0 ': cols), All (HasIn columns) subcolumns, AllUnique subcolumns) => NP (Aliased (Optional (Expression '[] commons Ungrouped schemas params '[tab ::: row, "excluded" ::: row]))) subcolumns -> [Condition '[] commons Ungrouped schemas params '[tab ::: row, "excluded" ::: row]] -> ConflictAction tab commons schemas params columns
- data UsingClause commons schemas params from where
- NoUsing :: UsingClause commons schemas params '[]
- Using :: FromClause '[] commons schemas params from -> UsingClause commons schemas params from
Manipulation
type family Manipulation_ (schemas :: SchemasType) (params :: Type) (row :: Type) where ... Source #
The top level Manipulation_
type is parameterized by a schemas
SchemasType
,
against which the query is type-checked, an input parameters
Haskell Type
,
and an ouput row Haskell Type
.
A top-level Manipulation_
can be run
using manipulateParams
, or if parameters = ()
using manipulate
.
Generally, parameters
will be a Haskell tuple or record whose entries
may be referenced using positional
parameter
s 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, DEFAULT)
parameterized insert:
>>>
type Columns = '["col1" ::: 'NoDef :=> 'NotNull 'PGint4, "col2" ::: 'NoDef :=> 'NotNull 'PGint4]
>>>
type Schema = '["tab" ::: 'Table ('[] :=> Columns)]
>>>
:{
let manipulation :: Manipulation_ (Public Schema) (Int32, Int32) () manipulation = insertInto_ #tab (Values_ (Set (param @1) `as` #col1 :* Set (param @2) `as` #col2)) in printSQL manipulation :} INSERT INTO "tab" ("col1", "col2") VALUES (($1 :: int4), ($2 :: 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, 3) 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', E'john@smith.com') ON CONFLICT ON CONSTRAINT "uq" DO UPDATE SET "email" = ("excluded"."email" || (E'; ' || "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 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"
Manipulation_ schemas params row = Manipulation '[] schemas (TuplePG params) (RowPG row) |
newtype Manipulation (commons :: FromType) (schemas :: SchemasType) (params :: [NullityType]) (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
Instances
With Manipulation Source # | |
Defined in Squeal.PostgreSQL.Manipulation with :: AlignedList (CommonTableExpression Manipulation schemas params) commons0 commons1 -> Manipulation commons1 schemas params row -> Manipulation commons0 schemas params row Source # | |
Eq (Manipulation commons schemas params columns) Source # | |
Defined in Squeal.PostgreSQL.Manipulation (==) :: Manipulation commons schemas params columns -> Manipulation commons schemas params columns -> Bool # (/=) :: Manipulation commons schemas params columns -> Manipulation commons schemas params columns -> Bool # | |
Ord (Manipulation commons schemas params columns) Source # | |
Defined in Squeal.PostgreSQL.Manipulation compare :: Manipulation commons schemas params columns -> Manipulation commons schemas params columns -> Ordering # (<) :: Manipulation commons schemas params columns -> Manipulation commons schemas params columns -> Bool # (<=) :: Manipulation commons schemas params columns -> Manipulation commons schemas params columns -> Bool # (>) :: Manipulation commons schemas params columns -> Manipulation commons schemas params columns -> Bool # (>=) :: Manipulation commons schemas params columns -> Manipulation commons schemas params columns -> Bool # max :: Manipulation commons schemas params columns -> Manipulation commons schemas params columns -> Manipulation commons schemas params columns # min :: Manipulation commons schemas params columns -> Manipulation commons schemas params columns -> Manipulation commons schemas params columns # | |
Show (Manipulation commons schemas params columns) Source # | |
Defined in Squeal.PostgreSQL.Manipulation showsPrec :: Int -> Manipulation commons schemas params columns -> ShowS # show :: Manipulation commons schemas params columns -> String # showList :: [Manipulation commons schemas params columns] -> ShowS # | |
Generic (Manipulation commons schemas params columns) Source # | |
Defined in Squeal.PostgreSQL.Manipulation type Rep (Manipulation commons schemas params columns) :: Type -> Type # from :: Manipulation commons schemas params columns -> Rep (Manipulation commons schemas params columns) x # to :: Rep (Manipulation commons schemas params columns) x -> Manipulation commons schemas params columns # | |
NFData (Manipulation commons schemas params columns) Source # | |
Defined in Squeal.PostgreSQL.Manipulation rnf :: Manipulation commons schemas params columns -> () # | |
RenderSQL (Manipulation commons schemas params columns) Source # | |
Defined in Squeal.PostgreSQL.Manipulation renderSQL :: Manipulation commons schemas params columns -> ByteString Source # | |
type Rep (Manipulation commons schemas params columns) Source # | |
Defined in Squeal.PostgreSQL.Manipulation type Rep (Manipulation commons schemas params columns) = D1 (MetaData "Manipulation" "Squeal.PostgreSQL.Manipulation" "squeal-postgresql-0.5.2.0-4fAomBtpMjd6mRwLthA4w2" True) (C1 (MetaCons "UnsafeManipulation" PrefixI True) (S1 (MetaSel (Just "renderManipulation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString))) |
queryStatement :: Query '[] commons schemas params columns -> Manipulation commons schemas params columns Source #
Convert a Query
into a Manipulation
.
Insert
insertInto :: (Has sch schemas schema, Has tab schema (Table table), columns ~ TableToColumns table, row0 ~ TableToRow table, SListI columns, SListI row1) => QualifiedAlias sch tab -> QueryClause commons schemas params columns -> ConflictClause tab commons schemas params table -> ReturningClause commons schemas params '[tab ::: row0] row1 -> Manipulation commons schemas params row1 Source #
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.
insertInto_ :: (Has sch schemas schema, Has tab schema (Table table), columns ~ TableToColumns table, row ~ TableToRow table, SListI columns) => QualifiedAlias sch tab -> QueryClause commons schemas params columns -> Manipulation commons schemas params '[] Source #
Like insertInto
but with OnConflictDoRaise
and no ReturningClause
.
Update
:: (SListI columns, SListI row1, db ~ (commons :=> schemas), Has sch schemas schema, Has tab schema (Table table), row0 ~ TableToRow table, columns ~ TableToColumns table, All (HasIn columns) subcolumns, AllUnique subcolumns) | |
=> QualifiedAlias sch tab | table to update |
-> NP (Aliased (Optional (Expression '[] '[] Ungrouped schemas params '[tab ::: row0]))) subcolumns | modified values to replace old values |
-> Condition '[] commons Ungrouped schemas params '[tab ::: row0] | condition under which to perform update on a row |
-> ReturningClause commons schemas params '[tab ::: row0] row1 | results to return |
-> Manipulation commons schemas params row1 |
An update
command changes the values of the specified columns
in all rows that satisfy the condition.
:: (SListI columns, db ~ (commons :=> schemas), Has sch schemas schema, Has tab schema (Table table), row ~ TableToRow table, columns ~ TableToColumns table, All (HasIn columns) subcolumns, AllUnique subcolumns) | |
=> QualifiedAlias sch tab | table to update |
-> NP (Aliased (Optional (Expression '[] '[] Ungrouped schemas params '[tab ::: row]))) subcolumns | modified values to replace old values |
-> Condition '[] commons Ungrouped schemas params '[tab ::: row] | condition under which to perform update on a row |
-> Manipulation commons schemas params '[] |
Update a row returning Nil
.
Delete
:: (SListI row1, db ~ (commons :=> schemas), Has sch schemas schema, Has tab schema (Table table), row0 ~ TableToRow table, columns ~ TableToColumns table) | |
=> QualifiedAlias sch tab | table to delete from |
-> UsingClause commons schemas params from | |
-> Condition '[] commons Ungrouped schemas params ((tab ::: row0) ': from) | condition under which to delete a row |
-> ReturningClause commons schemas params '[tab ::: row0] row1 | results to return |
-> Manipulation commons schemas params row1 |
Delete rows from a table.
:: (db ~ (commons :=> schemas), Has sch schemas schema, Has tab schema (Table table), row ~ TableToRow table, columns ~ TableToColumns table) | |
=> QualifiedAlias sch tab | table to delete from |
-> Condition '[] commons Ungrouped schemas params '[tab ::: row] | condition under which to delete a row |
-> Manipulation commons schemas params '[] |
Delete rows returning Nil
.
Clauses
data Optional expr ty where Source #
Optional
is either Default
or a value, parameterized by an appropriate
ColumnConstraint
.
data QueryClause commons schemas params columns where Source #
A QueryClause
describes what to insertInto
a table.
Values :: SListI columns => NP (Aliased (Optional (Expression '[] commons Ungrouped schemas params '[]))) columns -> [NP (Aliased (Optional (Expression '[] commons Ungrouped schemas params '[]))) columns] -> QueryClause commons schemas params columns |
|
Select :: SListI columns => NP (Aliased (Optional (Expression '[] commons grp schemas params from))) columns -> TableExpression '[] commons grp schemas params from -> QueryClause commons schemas params columns |
|
Subquery :: ColumnsToRow columns ~ row => Query '[] commons schemas params row -> QueryClause commons schemas params columns |
|
Instances
RenderSQL (QueryClause commons schemas params columns) Source # | |
Defined in Squeal.PostgreSQL.Manipulation renderSQL :: QueryClause commons schemas params columns -> ByteString Source # |
pattern Values_ :: SListI columns => NP (Aliased (Optional (Expression '[] commons Ungrouped schemas params '[]))) columns -> QueryClause commons schemas params columns Source #
Values_
describes a single NP
list of Aliased
Optional
Expression
s
whose ColumnsType
must match the tables'.
newtype ReturningClause commons schemas 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 commons schemas params from row) Source # | |
Defined in Squeal.PostgreSQL.Manipulation renderSQL :: ReturningClause commons schemas params from row -> ByteString Source # |
pattern Returning_ :: SListI row => NP (Aliased (Expression '[] commons Ungrouped schemas params from)) row -> ReturningClause commons schemas params from row Source #
data ConflictClause tab commons schemas 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.
OnConflictDoRaise :: ConflictClause tab commons schemas params table | |
OnConflict :: ConflictTarget constraints -> ConflictAction tab commons schemas params columns -> ConflictClause tab commons schemas params (constraints :=> columns) |
Instances
SListI (TableToColumns table) => RenderSQL (ConflictClause tab commons schemas params table) Source # | Render a |
Defined in Squeal.PostgreSQL.Manipulation renderSQL :: ConflictClause tab commons schemas params table -> ByteString Source # |
data ConflictTarget constraints where Source #
A ConflictTarget
specifies the constraint violation that triggers a
ConflictAction
.
OnConstraint :: Has con constraints constraint => Alias con -> ConflictTarget constraints |
Instances
RenderSQL (ConflictTarget constraints) Source # | Render a |
Defined in Squeal.PostgreSQL.Manipulation renderSQL :: ConflictTarget constraints -> ByteString Source # |
data ConflictAction tab commons schemas params columns 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 Condition
s in OnConflict
DoUpdate
have access to the
existing row using the table's name (or an alias), and to rows proposed
for insertion using the special #excluded
table.
DoNothing :: ConflictAction tab commons schemas params columns |
|
DoUpdate |
|
|
Instances
RenderSQL (ConflictAction tab commons schemas params columns) Source # | |
Defined in Squeal.PostgreSQL.Manipulation renderSQL :: ConflictAction tab commons schemas params columns -> ByteString Source # |
data UsingClause commons schemas params from where Source #
Specify additional tables.
NoUsing :: UsingClause commons schemas params '[] | No |
Using :: FromClause '[] commons schemas params from -> UsingClause commons schemas params from | An |