| Copyright | (c) Eitan Chatav 2017 |
|---|---|
| Maintainer | eitan@morphism.tech |
| Stability | experimental |
| Safe Haskell | None |
| Language | Haskell2010 |
Squeal.PostgreSQL.Definition
Contents
Description
Squeal data definition language.
- newtype Definition (schema0 :: TablesType) (schema1 :: TablesType) = UnsafeDefinition {}
- (>>>) :: Category k cat => cat a b -> cat b c -> cat a c
- createTable :: (KnownSymbol table, columns ~ (col ': cols), SListI columns, SListI constraints) => Alias table -> NP (Aliased TypeExpression) columns -> NP (Aliased (TableConstraintExpression schema columns)) constraints -> Definition schema (Create table (constraints :=> columns) schema)
- createTableIfNotExists :: (Has table schema (constraints :=> columns), SListI columns, SListI constraints) => Alias table -> NP (Aliased TypeExpression) columns -> NP (Aliased (TableConstraintExpression schema columns)) constraints -> Definition schema schema
- newtype TableConstraintExpression (schema :: TablesType) (columns :: ColumnsType) (tableConstraint :: TableConstraint) = UnsafeTableConstraintExpression {}
- data Column (columns :: ColumnsType) (column :: (Symbol, ColumnType)) where
- check :: NP (Column columns) subcolumns -> Condition '[table ::: ColumnsToRelation subcolumns] Ungrouped '[] -> TableConstraintExpression schema columns (Check (AliasesOf subcolumns))
- unique :: SListI subcolumns => NP (Column columns) subcolumns -> TableConstraintExpression schema columns (Unique (AliasesOf subcolumns))
- primaryKey :: (SListI subcolumns, AllNotNull subcolumns) => NP (Column columns) subcolumns -> TableConstraintExpression schema columns (PrimaryKey (AliasesOf subcolumns))
- foreignKey :: ForeignKeyed schema table reftable subcolumns refsubcolumns => NP (Column columns) subcolumns -> Alias table -> NP (Column (TableToColumns reftable)) refsubcolumns -> OnDeleteClause -> OnUpdateClause -> TableConstraintExpression schema columns (ForeignKey (AliasesOf subcolumns) table (AliasesOf refsubcolumns))
- type ForeignKeyed schema table reftable subcolumns refsubcolumns = (Has table schema reftable, SameTypes subcolumns refsubcolumns, AllNotNull subcolumns, SListI subcolumns, SListI refsubcolumns)
- data OnDeleteClause
- renderOnDeleteClause :: OnDeleteClause -> ByteString
- data OnUpdateClause
- renderOnUpdateClause :: OnUpdateClause -> ByteString
- dropTable :: KnownSymbol table => Alias table -> Definition schema (Drop table schema)
- alterTable :: Has tab schema table0 => Alias tab -> AlterTable schema table0 table1 -> Definition schema (Alter tab schema table1)
- alterTableRename :: (KnownSymbol table0, KnownSymbol table1) => Alias table0 -> Alias table1 -> Definition schema (Rename table0 table1 schema)
- newtype AlterTable (schema :: TablesType) (table0 :: TableType) (table1 :: TableType) = UnsafeAlterTable {}
- addConstraint :: KnownSymbol alias => Alias alias -> TableConstraintExpression schema columns constraint -> AlterTable schema (constraints :=> columns) (Create alias constraint constraints :=> columns)
- dropConstraint :: KnownSymbol constraint => Alias constraint -> AlterTable schema (constraints :=> columns) (Drop constraint constraints :=> columns)
- class AddColumn ty where
- dropColumn :: KnownSymbol column => Alias column -> AlterTable schema (constraints :=> columns) (DropIfConstraintsInvolve column constraints :=> Drop column columns)
- renameColumn :: (KnownSymbol column0, KnownSymbol column1) => Alias column0 -> Alias column1 -> AlterTable schema (constraints :=> columns) (constraints :=> Rename column0 column1 columns)
- alterColumn :: (KnownSymbol column, Has column columns ty0) => Alias column -> AlterColumn ty0 ty1 -> AlterTable schema (constraints :=> columns) (constraints :=> Alter column columns ty1)
- newtype AlterColumn (ty0 :: ColumnType) (ty1 :: ColumnType) = UnsafeAlterColumn {}
- setDefault :: Expression '[] Ungrouped '[] ty -> AlterColumn (constraint :=> ty) (Def :=> ty)
- dropDefault :: AlterColumn (Def :=> ty) (NoDef :=> ty)
- setNotNull :: AlterColumn (constraint :=> Null ty) (constraint :=> NotNull ty)
- dropNotNull :: AlterColumn (constraint :=> NotNull ty) (constraint :=> Null ty)
- alterType :: TypeExpression ty -> AlterColumn ty0 ty
Definition
newtype Definition (schema0 :: TablesType) (schema1 :: TablesType) Source #
A Definition is a statement that changes the schema of the
database, like a createTable, dropTable, or alterTable command.
Definitions may be composed using the >>> operator.
Constructors
| UnsafeDefinition | |
Fields | |
Instances
| Category TablesType Definition Source # | |
| Eq (Definition schema0 schema1) Source # | |
| Ord (Definition schema0 schema1) Source # | |
| Show (Definition schema0 schema1) Source # | |
| Generic (Definition schema0 schema1) Source # | |
| NFData (Definition schema0 schema1) Source # | |
| type Rep (Definition schema0 schema1) Source # | |
Create
Arguments
| :: (KnownSymbol table, columns ~ (col ': cols), SListI columns, SListI constraints) | |
| => Alias table | the name of the table to add |
| -> NP (Aliased TypeExpression) columns | the names and datatype of each column |
| -> NP (Aliased (TableConstraintExpression schema columns)) constraints | constraints that must hold for the table |
| -> Definition schema (Create table (constraints :=> columns) schema) |
createTable adds a table to the schema.
>>>:set -XOverloadedLabels>>>:{renderDefinition $ createTable #tab (int `As` #a :* real `As` #b :* Nil) Nil :} "CREATE TABLE tab (a int, b real);"
createTableIfNotExists Source #
Arguments
| :: (Has table schema (constraints :=> columns), SListI columns, SListI constraints) | |
| => Alias table | the name of the table to add |
| -> NP (Aliased TypeExpression) columns | the names and datatype of each column |
| -> NP (Aliased (TableConstraintExpression schema columns)) constraints | constraints that must hold for the table |
| -> Definition schema schema |
createTableIfNotExists creates a table if it doesn't exist, but does not add it to the schema.
Instead, the schema already has the table so if the table did not yet exist, the schema was wrong.
createTableIfNotExists fixes this. Interestingly, this property makes it an idempotent in the Category Definition.
>>>:set -XOverloadedLabels -XTypeApplications>>>type Table = '[] :=> '["a" ::: 'NoDef :=> 'Null 'PGint4, "b" ::: 'NoDef :=> 'Null 'PGfloat4]>>>type Schema = '["tab" ::: Table]>>>:{renderDefinition (createTableIfNotExists #tab (int `As` #a :* real `As` #b :* Nil) Nil :: Definition Schema Schema) :} "CREATE TABLE IF NOT EXISTS tab (a int, b real);"
newtype TableConstraintExpression (schema :: TablesType) (columns :: ColumnsType) (tableConstraint :: TableConstraint) Source #
Data types are a way to limit the kind of data that can be stored in a
table. For many applications, however, the constraint they provide is
too coarse. For example, a column containing a product price should
probably only accept positive values. But there is no standard data type
that accepts only positive numbers. Another issue is that you might want
to constrain column data with respect to other columns or rows.
For example, in a table containing product information,
there should be only one row for each product number.
TableConstraints give you as much control over the data in your tables
as you wish. If a user attempts to store data in a column that would
violate a constraint, an error is raised. This applies
even if the value came from the default value definition.
Constructors
| UnsafeTableConstraintExpression | |
Instances
| Eq (TableConstraintExpression schema columns tableConstraint) Source # | |
| Ord (TableConstraintExpression schema columns tableConstraint) Source # | |
| Show (TableConstraintExpression schema columns tableConstraint) Source # | |
| Generic (TableConstraintExpression schema columns tableConstraint) Source # | |
| NFData (TableConstraintExpression schema columns tableConstraint) Source # | |
| type Rep (TableConstraintExpression schema columns tableConstraint) Source # | |
data Column (columns :: ColumnsType) (column :: (Symbol, ColumnType)) where Source #
Column columns column is a witness that column is in columns.
Arguments
| :: NP (Column columns) subcolumns | |
| -> Condition '[table ::: ColumnsToRelation subcolumns] Ungrouped '[] | condition to check |
| -> TableConstraintExpression schema columns (Check (AliasesOf subcolumns)) |
A check constraint is the most generic TableConstraint type.
It allows you to specify that the value in a certain column must satisfy
a Boolean (truth-value) expression.
>>>:{renderDefinition $ createTable #tab ( (int & notNull) `As` #a :* (int & notNull) `As` #b :* Nil ) ( check (Column #a :* Column #b :* Nil) (#a .> #b) `As` #inequality :* Nil ) :} "CREATE TABLE tab (a int NOT NULL, b int NOT NULL, CONSTRAINT inequality CHECK ((a > b)));"
Arguments
| :: SListI subcolumns | |
| => NP (Column columns) subcolumns | unique column or group of columns |
| -> TableConstraintExpression schema columns (Unique (AliasesOf subcolumns)) |
A unique constraint ensure that the data contained in a column,
or a group of columns, is unique among all the rows in the table.
>>>:{renderDefinition $ createTable #tab ( int `As` #a :* int `As` #b :* Nil ) ( unique (Column #a :* Column #b :* Nil) `As` #uq_a_b :* Nil ) :} "CREATE TABLE tab (a int, b int, CONSTRAINT uq_a_b UNIQUE (a, b));"
Arguments
| :: (SListI subcolumns, AllNotNull subcolumns) | |
| => NP (Column columns) subcolumns | identifying column or group of columns |
| -> TableConstraintExpression schema columns (PrimaryKey (AliasesOf subcolumns)) |
A primaryKey constraint indicates that a column, or group of columns,
can be used as a unique identifier for rows in the table.
This requires that the values be both unique and not null.
>>>:{renderDefinition $ createTable #tab ( serial `As` #id :* (text & notNull) `As` #name :* Nil ) ( primaryKey (Column #id :* Nil) `As` #pk_id :* Nil ) :} "CREATE TABLE tab (id serial, name text NOT NULL, CONSTRAINT pk_id PRIMARY KEY (id));"
Arguments
| :: ForeignKeyed schema table reftable subcolumns refsubcolumns | |
| => NP (Column columns) subcolumns | column or columns in the table |
| -> Alias table | reference table |
| -> NP (Column (TableToColumns reftable)) refsubcolumns | reference column or columns in the reference table |
| -> OnDeleteClause | what to do when reference is deleted |
| -> OnUpdateClause | what to do when reference is updated |
| -> TableConstraintExpression schema columns (ForeignKey (AliasesOf subcolumns) table (AliasesOf refsubcolumns)) |
A foreignKey specifies that the values in a column
(or a group of columns) must match the values appearing in some row of
another table. We say this maintains the referential integrity
between two related tables.
>>>:{type Schema = '[ "users" ::: '[ "pk_users" ::: 'PrimaryKey '["id"] ] :=> '[ "id" ::: 'Def :=> 'NotNull 'PGint4 , "name" ::: 'NoDef :=> 'NotNull 'PGtext ] , "emails" ::: '[ "pk_emails" ::: 'PrimaryKey '["id"] , "fk_user_id" ::: 'ForeignKey '["user_id"] "users" '["id"] ] :=> '[ "id" ::: 'Def :=> 'NotNull 'PGint4 , "user_id" ::: 'NoDef :=> 'NotNull 'PGint4 , "email" ::: 'NoDef :=> 'Null 'PGtext ] ] :}
>>>:{let setup :: Definition '[] Schema setup = createTable #users ( serial `As` #id :* (text & notNull) `As` #name :* Nil ) ( primaryKey (Column #id :* Nil) `As` #pk_users :* Nil ) >>> createTable #emails ( serial `As` #id :* (int & notNull) `As` #user_id :* text `As` #email :* Nil ) ( primaryKey (Column #id :* Nil) `As` #pk_emails :* foreignKey (Column #user_id :* Nil) #users (Column #id :* Nil) OnDeleteCascade OnUpdateCascade `As` #fk_user_id :* Nil ) in renderDefinition setup :} "CREATE TABLE users (id serial, name text NOT NULL, CONSTRAINT pk_users PRIMARY KEY (id)); CREATE TABLE emails (id serial, user_id int NOT NULL, email text, CONSTRAINT pk_emails PRIMARY KEY (id), CONSTRAINT fk_user_id FOREIGN KEY (user_id) REFERENCES users (id) ON DELETE CASCADE ON UPDATE CASCADE);"
type ForeignKeyed schema table reftable subcolumns refsubcolumns = (Has table schema reftable, SameTypes subcolumns refsubcolumns, AllNotNull subcolumns, SListI subcolumns, SListI refsubcolumns) Source #
A type synonym for constraints on a table with a foreign key.
data OnDeleteClause Source #
OnDeleteClause indicates what to do with rows that reference a deleted row.
Constructors
| OnDeleteNoAction | if any referencing rows still exist when the constraint is checked, an error is raised |
| OnDeleteRestrict | prevents deletion of a referenced row |
| OnDeleteCascade | specifies that when a referenced row is deleted, row(s) referencing it should be automatically deleted as well |
Instances
renderOnDeleteClause :: OnDeleteClause -> ByteString Source #
Render OnDeleteClause.
data OnUpdateClause Source #
Analagous to OnDeleteClause there is also OnUpdateClause which is invoked
when a referenced column is changed (updated).
Constructors
| OnUpdateNoAction | if any referencing rows has not changed when the constraint is checked, an error is raised |
| OnUpdateRestrict | prevents update of a referenced row |
| OnUpdateCascade | the updated values of the referenced column(s) should be copied into the referencing row(s) |
Instances
renderOnUpdateClause :: OnUpdateClause -> ByteString Source #
Render OnUpdateClause.
Drop
Arguments
| :: KnownSymbol table | |
| => Alias table | table to remove |
| -> Definition schema (Drop table schema) |
dropTable removes a table from the schema.
>>>renderDefinition $ dropTable #muh_table"DROP TABLE muh_table;"
Alter
Arguments
| :: Has tab schema table0 | |
| => Alias tab | table to alter |
| -> AlterTable schema table0 table1 | alteration to perform |
| -> Definition schema (Alter tab schema table1) |
alterTable changes the definition of a table from the schema.
Arguments
| :: (KnownSymbol table0, KnownSymbol table1) | |
| => Alias table0 | table to rename |
| -> Alias table1 | what to rename it |
| -> Definition schema (Rename table0 table1 schema) |
alterTableRename changes the name of a table from the schema.
>>>renderDefinition $ alterTableRename #foo #bar"ALTER TABLE foo RENAME TO bar;"
newtype AlterTable (schema :: TablesType) (table0 :: TableType) (table1 :: TableType) Source #
An AlterTable describes the alteration to perform on the columns
of a table.
Constructors
| UnsafeAlterTable | |
Fields | |
Instances
| Eq (AlterTable schema table0 table1) Source # | |
| Ord (AlterTable schema table0 table1) Source # | |
| Show (AlterTable schema table0 table1) Source # | |
| Generic (AlterTable schema table0 table1) Source # | |
| NFData (AlterTable schema table0 table1) Source # | |
| type Rep (AlterTable schema table0 table1) Source # | |
Arguments
| :: KnownSymbol alias | |
| => Alias alias | |
| -> TableConstraintExpression schema columns constraint | constraint to add |
| -> AlterTable schema (constraints :=> columns) (Create alias constraint constraints :=> columns) |
An addConstraint adds a table constraint.
>>>:{let definition :: Definition '["tab" ::: '[] :=> '["col" ::: 'NoDef :=> 'NotNull 'PGint4]] '["tab" ::: '["positive" ::: Check '["col"]] :=> '["col" ::: 'NoDef :=> 'NotNull 'PGint4]] definition = alterTable #tab (addConstraint #positive (check (Column #col :* Nil) (#col .> 0))) in renderDefinition definition :} "ALTER TABLE tab ADD CONSTRAINT positive CHECK ((col > 0));"
Arguments
| :: KnownSymbol constraint | |
| => Alias constraint | constraint to drop |
| -> AlterTable schema (constraints :=> columns) (Drop constraint constraints :=> columns) |
A dropConstraint drops a table constraint.
>>>:{let definition :: Definition '["tab" ::: '["positive" ::: Check '["col"]] :=> '["col" ::: 'NoDef :=> 'NotNull 'PGint4]] '["tab" ::: '[] :=> '["col" ::: 'NoDef :=> 'NotNull 'PGint4]] definition = alterTable #tab (dropConstraint #positive) in renderDefinition definition :} "ALTER TABLE tab DROP CONSTRAINT positive;"
class AddColumn ty where Source #
An AddColumn is either NULL or has DEFAULT.
Methods
Arguments
| :: KnownSymbol column | |
| => Alias column | column to add |
| -> TypeExpression ty | type of the new column |
| -> AlterTable schema (constraints :=> columns) (constraints :=> Create column ty columns) |
addColumn adds a new column, initially filled with whatever
default value is given or with NULL.
>>>:{let definition :: Definition '["tab" ::: '[] :=> '["col1" ::: 'NoDef :=> 'Null 'PGint4]] '["tab" ::: '[] :=> '[ "col1" ::: 'NoDef :=> 'Null 'PGint4 , "col2" ::: 'Def :=> 'Null 'PGtext ]] definition = alterTable #tab (addColumn #col2 (text & default_ "foo")) in renderDefinition definition :} "ALTER TABLE tab ADD COLUMN col2 text DEFAULT E'foo';"
>>>:{let definition :: Definition '["tab" ::: '[] :=> '["col1" ::: 'NoDef :=> 'Null 'PGint4]] '["tab" ::: '[] :=> '[ "col1" ::: 'NoDef :=> 'Null 'PGint4 , "col2" ::: 'NoDef :=> 'Null 'PGtext ]] definition = alterTable #tab (addColumn #col2 text) in renderDefinition definition :} "ALTER TABLE tab ADD COLUMN col2 text;"
Instances
Arguments
| :: KnownSymbol column | |
| => Alias column | column to remove |
| -> AlterTable schema (constraints :=> columns) (DropIfConstraintsInvolve column constraints :=> Drop column columns) |
A dropColumn removes a column. Whatever data was in the column
disappears. Table constraints involving the column are dropped, too.
However, if the column is referenced by a foreign key constraint of
another table, PostgreSQL will not silently drop that constraint.
>>>:{let definition :: Definition '["tab" ::: '[] :=> '[ "col1" ::: 'NoDef :=> 'Null 'PGint4 , "col2" ::: 'NoDef :=> 'Null 'PGtext ]] '["tab" ::: '[] :=> '["col1" ::: 'NoDef :=> 'Null 'PGint4]] definition = alterTable #tab (dropColumn #col2) in renderDefinition definition :} "ALTER TABLE tab DROP COLUMN col2;"
Arguments
| :: (KnownSymbol column0, KnownSymbol column1) | |
| => Alias column0 | column to rename |
| -> Alias column1 | what to rename the column |
| -> AlterTable schema (constraints :=> columns) (constraints :=> Rename column0 column1 columns) |
A renameColumn renames a column.
>>>:{let definition :: Definition '["tab" ::: '[] :=> '["foo" ::: 'NoDef :=> 'Null 'PGint4]] '["tab" ::: '[] :=> '["bar" ::: 'NoDef :=> 'Null 'PGint4]] definition = alterTable #tab (renameColumn #foo #bar) in renderDefinition definition :} "ALTER TABLE tab RENAME COLUMN foo TO bar;"
Arguments
| :: (KnownSymbol column, Has column columns ty0) | |
| => Alias column | column to alter |
| -> AlterColumn ty0 ty1 | alteration to perform |
| -> AlterTable schema (constraints :=> columns) (constraints :=> Alter column columns ty1) |
An alterColumn alters a single column.
newtype AlterColumn (ty0 :: ColumnType) (ty1 :: ColumnType) Source #
An AlterColumn describes the alteration to perform on a single column.
Constructors
| UnsafeAlterColumn | |
Fields | |
Instances
| Eq (AlterColumn ty0 ty1) Source # | |
| Ord (AlterColumn ty0 ty1) Source # | |
| Show (AlterColumn ty0 ty1) Source # | |
| Generic (AlterColumn ty0 ty1) Source # | |
| NFData (AlterColumn ty0 ty1) Source # | |
| type Rep (AlterColumn ty0 ty1) Source # | |
Arguments
| :: Expression '[] Ungrouped '[] ty | default value to set |
| -> AlterColumn (constraint :=> ty) (Def :=> ty) |
A setDefault sets a new default for a column. Note that this doesn't
affect any existing rows in the table, it just changes the default for
future insert and update commands.
>>>:{let definition :: Definition '["tab" ::: '[] :=> '["col" ::: 'NoDef :=> 'Null 'PGint4]] '["tab" ::: '[] :=> '["col" ::: 'Def :=> 'Null 'PGint4]] definition = alterTable #tab (alterColumn #col (setDefault 5)) in renderDefinition definition :} "ALTER TABLE tab ALTER COLUMN col SET DEFAULT 5;"
dropDefault :: AlterColumn (Def :=> ty) (NoDef :=> ty) Source #
A dropDefault removes any default value for a column.
>>>:{let definition :: Definition '["tab" ::: '[] :=> '["col" ::: 'Def :=> 'Null 'PGint4]] '["tab" ::: '[] :=> '["col" ::: 'NoDef :=> 'Null 'PGint4]] definition = alterTable #tab (alterColumn #col dropDefault) in renderDefinition definition :} "ALTER TABLE tab ALTER COLUMN col DROP DEFAULT;"
setNotNull :: AlterColumn (constraint :=> Null ty) (constraint :=> NotNull ty) Source #
A setNotNull adds a NOT NULL constraint to a column.
The constraint will be checked immediately, so the table data must satisfy
the constraint before it can be added.
>>>:{let definition :: Definition '["tab" ::: '[] :=> '["col" ::: 'NoDef :=> 'Null 'PGint4]] '["tab" ::: '[] :=> '["col" ::: 'NoDef :=> 'NotNull 'PGint4]] definition = alterTable #tab (alterColumn #col setNotNull) in renderDefinition definition :} "ALTER TABLE tab ALTER COLUMN col SET NOT NULL;"
dropNotNull :: AlterColumn (constraint :=> NotNull ty) (constraint :=> Null ty) Source #
A dropNotNull drops a NOT NULL constraint from a column.
>>>:{let definition :: Definition '["tab" ::: '[] :=> '["col" ::: 'NoDef :=> 'NotNull 'PGint4]] '["tab" ::: '[] :=> '["col" ::: 'NoDef :=> 'Null 'PGint4]] definition = alterTable #tab (alterColumn #col dropNotNull) in renderDefinition definition :} "ALTER TABLE tab ALTER COLUMN col DROP NOT NULL;"
alterType :: TypeExpression ty -> AlterColumn ty0 ty Source #
An alterType converts a column to a different data type.
This will succeed only if each existing entry in the column can be
converted to the new type by an implicit cast.
>>>:{let definition :: Definition '["tab" ::: '[] :=> '["col" ::: 'NoDef :=> 'NotNull 'PGint4]] '["tab" ::: '[] :=> '["col" ::: 'NoDef :=> 'NotNull 'PGnumeric]] definition = alterTable #tab (alterColumn #col (alterType (numeric & notNull))) in renderDefinition definition :} "ALTER TABLE tab ALTER COLUMN col TYPE numeric NOT NULL;"