Copyright | (c) Eitan Chatav 2017 |
---|---|
Maintainer | [email protected] |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Squeal.PostgreSQL.Definition
Description
Squeal data definition language.
Synopsis
- newtype Definition (schema0 :: SchemaType) (schema1 :: SchemaType) = UnsafeDefinition {}
- (>>>) :: Category cat => cat a b -> cat b c -> cat a c
- createTable :: (KnownSymbol table, columns ~ (col ': cols), SListI columns, SListI constraints, schema1 ~ Create table (Table (constraints :=> columns)) schema0) => Alias table -> NP (Aliased (ColumnTypeExpression schema0)) columns -> NP (Aliased (TableConstraintExpression schema1 table)) constraints -> Definition schema0 schema1
- createTableIfNotExists :: (Has table schema (Table (constraints :=> columns)), SListI columns, SListI constraints) => Alias table -> NP (Aliased (ColumnTypeExpression schema)) columns -> NP (Aliased (TableConstraintExpression schema table)) constraints -> Definition schema schema
- newtype TableConstraintExpression (schema :: SchemaType) (table :: Symbol) (tableConstraint :: TableConstraint) = UnsafeTableConstraintExpression {}
- check :: (Has alias schema (Table table), HasAll aliases (TableToRelation table) subcolumns) => NP Alias aliases -> (forall tab. Condition schema '[tab ::: subcolumns] Ungrouped '[]) -> TableConstraintExpression schema alias (Check aliases)
- unique :: (Has alias schema (Table table), HasAll aliases (TableToRelation table) subcolumns) => NP Alias aliases -> TableConstraintExpression schema alias (Unique aliases)
- primaryKey :: (Has alias schema (Table table), HasAll aliases (TableToColumns table) subcolumns, AllNotNull subcolumns) => NP Alias aliases -> TableConstraintExpression schema alias (PrimaryKey aliases)
- foreignKey :: ForeignKeyed schema child parent table reftable columns refcolumns constraints cols reftys tys => NP Alias columns -> Alias parent -> NP Alias refcolumns -> OnDeleteClause -> OnUpdateClause -> TableConstraintExpression schema child (ForeignKey columns parent refcolumns)
- type ForeignKeyed schema child parent table reftable columns refcolumns constraints cols reftys tys = (Has child schema (Table table), Has parent schema (Table reftable), HasAll columns (TableToColumns table) tys, reftable ~ (constraints :=> cols), HasAll refcolumns cols reftys, AllZip SamePGType tys reftys, Uniquely refcolumns constraints)
- data OnDeleteClause
- renderOnDeleteClause :: OnDeleteClause -> ByteString
- data OnUpdateClause
- renderOnUpdateClause :: OnUpdateClause -> ByteString
- dropTable :: Has table schema (Table t) => Alias table -> Definition schema (Drop table schema)
- alterTable :: KnownSymbol alias => Alias alias -> AlterTable alias table schema -> Definition schema (Alter alias (Table table) schema)
- alterTableRename :: (KnownSymbol table0, KnownSymbol table1) => Alias table0 -> Alias table1 -> Definition schema (Rename table0 table1 schema)
- newtype AlterTable (alias :: Symbol) (table :: TableType) (schema :: SchemaType) = UnsafeAlterTable {}
- addConstraint :: (KnownSymbol alias, Has tab schema (Table table0), table0 ~ (constraints :=> columns), table1 ~ (Create alias constraint constraints :=> columns)) => Alias alias -> TableConstraintExpression schema tab constraint -> AlterTable tab table1 schema
- dropConstraint :: (KnownSymbol constraint, Has tab schema (Table table0), table0 ~ (constraints :=> columns), table1 ~ (Drop constraint constraints :=> columns)) => Alias constraint -> AlterTable tab table1 schema
- class AddColumn ty where
- dropColumn :: (KnownSymbol column, Has tab schema (Table table0), table0 ~ (constraints :=> columns), table1 ~ (constraints :=> Drop column columns)) => Alias column -> AlterTable tab table1 schema
- renameColumn :: (KnownSymbol column0, KnownSymbol column1, Has tab schema (Table table0), table0 ~ (constraints :=> columns), table1 ~ (constraints :=> Rename column0 column1 columns)) => Alias column0 -> Alias column1 -> AlterTable tab table1 schema
- alterColumn :: (KnownSymbol column, Has tab schema (Table table0), table0 ~ (constraints :=> columns), Has column columns ty0, tables1 ~ (constraints :=> Alter column ty1 columns)) => Alias column -> AlterColumn schema ty0 ty1 -> AlterTable tab table1 schema
- newtype AlterColumn (schema :: SchemaType) (ty0 :: ColumnType) (ty1 :: ColumnType) = UnsafeAlterColumn {}
- setDefault :: Expression schema '[] Ungrouped '[] ty -> AlterColumn schema (constraint :=> ty) (Def :=> ty)
- dropDefault :: AlterColumn schema (Def :=> ty) (NoDef :=> ty)
- setNotNull :: AlterColumn schema (constraint :=> Null ty) (constraint :=> NotNull ty)
- dropNotNull :: AlterColumn schema (constraint :=> NotNull ty) (constraint :=> Null ty)
- alterType :: ColumnTypeExpression schema ty -> AlterColumn schema ty0 ty
- createView :: KnownSymbol view => Alias view -> Query schema '[] relation -> Definition schema (Create view (View relation) schema)
- dropView :: Has view schema (View v) => Alias view -> Definition schema (Drop view schema)
- createTypeEnum :: (KnownSymbol enum, All KnownSymbol labels) => Alias enum -> NP PGlabel labels -> Definition schema (Create enum (Typedef (PGenum labels)) schema)
- createTypeEnumFrom :: forall hask enum schema. (Generic hask, All KnownSymbol (LabelsFrom hask), KnownSymbol enum) => Alias enum -> Definition schema (Create enum (Typedef (EnumFrom hask)) schema)
- createTypeComposite :: (KnownSymbol ty, SListI fields) => Alias ty -> NP (Aliased (TypeExpression schema)) fields -> Definition schema (Create ty (Typedef (PGcomposite fields)) schema)
- createTypeCompositeFrom :: forall hask ty schema. (ZipAliased (FieldNamesFrom hask) (FieldTypesFrom hask), All (PGTyped schema) (FieldTypesFrom hask), KnownSymbol ty) => Alias ty -> Definition schema (Create ty (Typedef (CompositeFrom hask)) schema)
- dropType :: Has tydef schema (Typedef ty) => Alias tydef -> Definition schema (Drop tydef schema)
- newtype ColumnTypeExpression (schema :: SchemaType) (ty :: ColumnType) = UnsafeColumnTypeExpression {}
- nullable :: TypeExpression schema ty -> ColumnTypeExpression schema (NoDef :=> Null ty)
- notNullable :: TypeExpression schema ty -> ColumnTypeExpression schema (def :=> NotNull ty)
- default_ :: Expression schema '[] Ungrouped '[] ty -> ColumnTypeExpression schema (NoDef :=> ty) -> ColumnTypeExpression schema (Def :=> ty)
- serial2 :: ColumnTypeExpression schema (Def :=> NotNull PGint2)
- smallserial :: ColumnTypeExpression schema (Def :=> NotNull PGint2)
- serial4 :: ColumnTypeExpression schema (Def :=> NotNull PGint4)
- serial :: ColumnTypeExpression schema (Def :=> NotNull PGint4)
- serial8 :: ColumnTypeExpression schema (Def :=> NotNull PGint8)
- bigserial :: ColumnTypeExpression schema (Def :=> NotNull PGint8)
Definition
newtype Definition (schema0 :: SchemaType) (schema1 :: SchemaType) Source #
A Definition
is a statement that changes the schema of the
database, like a createTable
, dropTable
, or alterTable
command.
Definition
s may be composed using the >>>
operator.
Constructors
UnsafeDefinition | |
Fields |
Instances
Category Definition Source # | |
Defined in Squeal.PostgreSQL.Definition | |
Eq (Definition schema0 schema1) Source # | |
Defined in Squeal.PostgreSQL.Definition Methods (==) :: Definition schema0 schema1 -> Definition schema0 schema1 -> Bool # (/=) :: Definition schema0 schema1 -> Definition schema0 schema1 -> Bool # | |
Ord (Definition schema0 schema1) Source # | |
Defined in Squeal.PostgreSQL.Definition Methods compare :: Definition schema0 schema1 -> Definition schema0 schema1 -> Ordering # (<) :: Definition schema0 schema1 -> Definition schema0 schema1 -> Bool # (<=) :: Definition schema0 schema1 -> Definition schema0 schema1 -> Bool # (>) :: Definition schema0 schema1 -> Definition schema0 schema1 -> Bool # (>=) :: Definition schema0 schema1 -> Definition schema0 schema1 -> Bool # max :: Definition schema0 schema1 -> Definition schema0 schema1 -> Definition schema0 schema1 # min :: Definition schema0 schema1 -> Definition schema0 schema1 -> Definition schema0 schema1 # | |
Show (Definition schema0 schema1) Source # | |
Defined in Squeal.PostgreSQL.Definition Methods showsPrec :: Int -> Definition schema0 schema1 -> ShowS # show :: Definition schema0 schema1 -> String # showList :: [Definition schema0 schema1] -> ShowS # | |
Generic (Definition schema0 schema1) Source # | |
Defined in Squeal.PostgreSQL.Definition Associated Types type Rep (Definition schema0 schema1) :: * -> * # Methods from :: Definition schema0 schema1 -> Rep (Definition schema0 schema1) x # to :: Rep (Definition schema0 schema1) x -> Definition schema0 schema1 # | |
NFData (Definition schema0 schema1) Source # | |
Defined in Squeal.PostgreSQL.Definition Methods rnf :: Definition schema0 schema1 -> () # | |
RenderSQL (Definition schema0 schema1) Source # | |
Defined in Squeal.PostgreSQL.Definition Methods renderSQL :: Definition schema0 schema1 -> ByteString Source # | |
type Rep (Definition schema0 schema1) Source # | |
Defined in Squeal.PostgreSQL.Definition type Rep (Definition schema0 schema1) = D1 (MetaData "Definition" "Squeal.PostgreSQL.Definition" "squeal-postgresql-0.3.1.0-DNDeh0HTANH3vXYqblRMwD" True) (C1 (MetaCons "UnsafeDefinition" PrefixI True) (S1 (MetaSel (Just "renderDefinition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString))) |
Tables
Create
Arguments
:: (KnownSymbol table, columns ~ (col ': cols), SListI columns, SListI constraints, schema1 ~ Create table (Table (constraints :=> columns)) schema0) | |
=> Alias table | the name of the table to add |
-> NP (Aliased (ColumnTypeExpression schema0)) columns | the names and datatype of each column |
-> NP (Aliased (TableConstraintExpression schema1 table)) constraints | constraints that must hold for the table |
-> Definition schema0 schema1 |
createTable
adds a table to the schema.
>>>
:set -XOverloadedLabels
>>>
:{
type Table = '[] :=> '[ "a" ::: 'NoDef :=> 'Null 'PGint4 , "b" ::: 'NoDef :=> 'Null 'PGfloat4 ] :}
>>>
:{
let setup :: Definition '[] '["tab" ::: 'Table Table] setup = createTable #tab (nullable int `as` #a :* nullable real `as` #b) Nil in printSQL setup :} CREATE TABLE "tab" ("a" int NULL, "b" real NULL);
createTableIfNotExists Source #
Arguments
:: (Has table schema (Table (constraints :=> columns)), SListI columns, SListI constraints) | |
=> Alias table | the name of the table to add |
-> NP (Aliased (ColumnTypeExpression schema)) columns | the names and datatype of each column |
-> NP (Aliased (TableConstraintExpression schema table)) 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
of Definition
s.
>>>
:set -XOverloadedLabels -XTypeApplications
>>>
:{
type Table = '[] :=> '[ "a" ::: 'NoDef :=> 'Null 'PGint4 , "b" ::: 'NoDef :=> 'Null 'PGfloat4 ] :}
>>>
type Schema = '["tab" ::: 'Table Table]
>>>
:{
let setup :: Definition Schema Schema setup = createTableIfNotExists #tab (nullable int `as` #a :* nullable real `as` #b) Nil in printSQL setup :} CREATE TABLE IF NOT EXISTS "tab" ("a" int NULL, "b" real NULL);
newtype TableConstraintExpression (schema :: SchemaType) (table :: Symbol) (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.
TableConstraint
s 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 table tableConstraint) Source # | |
Defined in Squeal.PostgreSQL.Definition Methods (==) :: TableConstraintExpression schema table tableConstraint -> TableConstraintExpression schema table tableConstraint -> Bool # (/=) :: TableConstraintExpression schema table tableConstraint -> TableConstraintExpression schema table tableConstraint -> Bool # | |
Ord (TableConstraintExpression schema table tableConstraint) Source # | |
Defined in Squeal.PostgreSQL.Definition Methods compare :: TableConstraintExpression schema table tableConstraint -> TableConstraintExpression schema table tableConstraint -> Ordering # (<) :: TableConstraintExpression schema table tableConstraint -> TableConstraintExpression schema table tableConstraint -> Bool # (<=) :: TableConstraintExpression schema table tableConstraint -> TableConstraintExpression schema table tableConstraint -> Bool # (>) :: TableConstraintExpression schema table tableConstraint -> TableConstraintExpression schema table tableConstraint -> Bool # (>=) :: TableConstraintExpression schema table tableConstraint -> TableConstraintExpression schema table tableConstraint -> Bool # max :: TableConstraintExpression schema table tableConstraint -> TableConstraintExpression schema table tableConstraint -> TableConstraintExpression schema table tableConstraint # min :: TableConstraintExpression schema table tableConstraint -> TableConstraintExpression schema table tableConstraint -> TableConstraintExpression schema table tableConstraint # | |
Show (TableConstraintExpression schema table tableConstraint) Source # | |
Defined in Squeal.PostgreSQL.Definition Methods showsPrec :: Int -> TableConstraintExpression schema table tableConstraint -> ShowS # show :: TableConstraintExpression schema table tableConstraint -> String # showList :: [TableConstraintExpression schema table tableConstraint] -> ShowS # | |
Generic (TableConstraintExpression schema table tableConstraint) Source # | |
Defined in Squeal.PostgreSQL.Definition Associated Types type Rep (TableConstraintExpression schema table tableConstraint) :: * -> * # Methods from :: TableConstraintExpression schema table tableConstraint -> Rep (TableConstraintExpression schema table tableConstraint) x # to :: Rep (TableConstraintExpression schema table tableConstraint) x -> TableConstraintExpression schema table tableConstraint # | |
NFData (TableConstraintExpression schema table tableConstraint) Source # | |
Defined in Squeal.PostgreSQL.Definition Methods rnf :: TableConstraintExpression schema table tableConstraint -> () # | |
type Rep (TableConstraintExpression schema table tableConstraint) Source # | |
Defined in Squeal.PostgreSQL.Definition type Rep (TableConstraintExpression schema table tableConstraint) = D1 (MetaData "TableConstraintExpression" "Squeal.PostgreSQL.Definition" "squeal-postgresql-0.3.1.0-DNDeh0HTANH3vXYqblRMwD" True) (C1 (MetaCons "UnsafeTableConstraintExpression" PrefixI True) (S1 (MetaSel (Just "renderTableConstraintExpression") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString))) |
Arguments
:: (Has alias schema (Table table), HasAll aliases (TableToRelation table) subcolumns) | |
=> NP Alias aliases | specify the subcolumns which are getting checked |
-> (forall tab. Condition schema '[tab ::: subcolumns] Ungrouped '[]) | a closed |
-> TableConstraintExpression schema alias (Check aliases) |
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.
>>>
:{
type Schema = '[ "tab" ::: 'Table ('[ "inequality" ::: 'Check '["a","b"]] :=> '[ "a" ::: 'NoDef :=> 'NotNull 'PGint4, "b" ::: 'NoDef :=> 'NotNull 'PGint4 ])] :}
>>>
:{
let definition :: Definition '[] Schema definition = createTable #tab ( (int & notNullable) `as` #a :* (int & notNullable) `as` #b ) ( check (#a :* #b) (#a .> #b) `as` #inequality ) :}
>>>
printSQL definition
CREATE TABLE "tab" ("a" int NOT NULL, "b" int NOT NULL, CONSTRAINT "inequality" CHECK (("a" > "b")));
Arguments
:: (Has alias schema (Table table), HasAll aliases (TableToRelation table) subcolumns) | |
=> NP Alias aliases | specify subcolumns which together are unique for each row |
-> TableConstraintExpression schema alias (Unique aliases) |
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.
>>>
:{
type Schema = '[ "tab" ::: 'Table( '[ "uq_a_b" ::: 'Unique '["a","b"]] :=> '[ "a" ::: 'NoDef :=> 'Null 'PGint4, "b" ::: 'NoDef :=> 'Null 'PGint4 ])] :}
>>>
:{
let definition :: Definition '[] Schema definition = createTable #tab ( (int & nullable) `as` #a :* (int & nullable) `as` #b ) ( unique (#a :* #b) `as` #uq_a_b ) :}
>>>
printSQL definition
CREATE TABLE "tab" ("a" int NULL, "b" int NULL, CONSTRAINT "uq_a_b" UNIQUE ("a", "b"));
Arguments
:: (Has alias schema (Table table), HasAll aliases (TableToColumns table) subcolumns, AllNotNull subcolumns) | |
=> NP Alias aliases | specify the subcolumns which together form a primary key. |
-> TableConstraintExpression schema alias (PrimaryKey aliases) |
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.
>>>
:{
type Schema = '[ "tab" ::: 'Table ('[ "pk_id" ::: 'PrimaryKey '["id"]] :=> '[ "id" ::: 'Def :=> 'NotNull 'PGint4, "name" ::: 'NoDef :=> 'NotNull 'PGtext ])] :}
>>>
:{
let definition :: Definition '[] Schema definition = createTable #tab ( serial `as` #id :* (text & notNullable) `as` #name ) ( primaryKey #id `as` #pk_id ) :}
>>>
printSQL definition
CREATE TABLE "tab" ("id" serial, "name" text NOT NULL, CONSTRAINT "pk_id" PRIMARY KEY ("id"));
Arguments
:: ForeignKeyed schema child parent table reftable columns refcolumns constraints cols reftys tys | |
=> NP Alias columns | column or columns in the table |
-> Alias parent | reference table |
-> NP Alias refcolumns | 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 child (ForeignKey columns parent refcolumns) |
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" ::: 'Table ( '[ "pk_users" ::: 'PrimaryKey '["id"] ] :=> '[ "id" ::: 'Def :=> 'NotNull 'PGint4 , "name" ::: 'NoDef :=> 'NotNull 'PGtext ]) , "emails" ::: 'Table ( '[ "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 & notNullable) `as` #name ) ( primaryKey #id `as` #pk_users ) >>> createTable #emails ( serial `as` #id :* (int & notNullable) `as` #user_id :* (text & nullable) `as` #email ) ( primaryKey #id `as` #pk_emails :* foreignKey #user_id #users #id OnDeleteCascade OnUpdateCascade `as` #fk_user_id ) in printSQL 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 NULL, CONSTRAINT "pk_emails" PRIMARY KEY ("id"), CONSTRAINT "fk_user_id" FOREIGN KEY ("user_id") REFERENCES "users" ("id") ON DELETE CASCADE ON UPDATE CASCADE);
A foreignKey
can even be a table self-reference.
>>>
:{
type Schema = '[ "employees" ::: 'Table ( '[ "employees_pk" ::: 'PrimaryKey '["id"] , "employees_employer_fk" ::: 'ForeignKey '["employer_id"] "employees" '["id"] ] :=> '[ "id" ::: 'Def :=> 'NotNull 'PGint4 , "name" ::: 'NoDef :=> 'NotNull 'PGtext , "employer_id" ::: 'NoDef :=> 'Null 'PGint4 ]) ] :}
>>>
:{
let setup :: Definition '[] Schema setup = createTable #employees ( serial `as` #id :* (text & notNullable) `as` #name :* (integer & nullable) `as` #employer_id ) ( primaryKey #id `as` #employees_pk :* foreignKey #employer_id #employees #id OnDeleteCascade OnUpdateCascade `as` #employees_employer_fk ) in printSQL setup :} CREATE TABLE "employees" ("id" serial, "name" text NOT NULL, "employer_id" integer NULL, CONSTRAINT "employees_pk" PRIMARY KEY ("id"), CONSTRAINT "employees_employer_fk" FOREIGN KEY ("employer_id") REFERENCES "employees" ("id") ON DELETE CASCADE ON UPDATE CASCADE);
type ForeignKeyed schema child parent table reftable columns refcolumns constraints cols reftys tys = (Has child schema (Table table), Has parent schema (Table reftable), HasAll columns (TableToColumns table) tys, reftable ~ (constraints :=> cols), HasAll refcolumns cols reftys, AllZip SamePGType tys reftys, Uniquely refcolumns constraints) Source #
A constraint synonym between types involved in a foreign key constraint.
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
:: Has table schema (Table t) | |
=> Alias table | table to remove |
-> Definition schema (Drop table schema) |
dropTable
removes a table from the schema.
>>>
:{
let definition :: Definition '["muh_table" ::: 'Table t] '[] definition = dropTable #muh_table :}
>>>
printSQL definition
DROP TABLE "muh_table";
Alter
Arguments
:: KnownSymbol alias | |
=> Alias alias | table to alter |
-> AlterTable alias table schema | alteration to perform |
-> Definition schema (Alter alias (Table table) schema) |
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.
>>>
printSQL $ alterTableRename #foo #bar
ALTER TABLE "foo" RENAME TO "bar";
newtype AlterTable (alias :: Symbol) (table :: TableType) (schema :: SchemaType) Source #
An AlterTable
describes the alteration to perform on the columns
of a table.
Constructors
UnsafeAlterTable | |
Fields |
Instances
Eq (AlterTable alias table schema) Source # | |
Defined in Squeal.PostgreSQL.Definition Methods (==) :: AlterTable alias table schema -> AlterTable alias table schema -> Bool # (/=) :: AlterTable alias table schema -> AlterTable alias table schema -> Bool # | |
Ord (AlterTable alias table schema) Source # | |
Defined in Squeal.PostgreSQL.Definition Methods compare :: AlterTable alias table schema -> AlterTable alias table schema -> Ordering # (<) :: AlterTable alias table schema -> AlterTable alias table schema -> Bool # (<=) :: AlterTable alias table schema -> AlterTable alias table schema -> Bool # (>) :: AlterTable alias table schema -> AlterTable alias table schema -> Bool # (>=) :: AlterTable alias table schema -> AlterTable alias table schema -> Bool # max :: AlterTable alias table schema -> AlterTable alias table schema -> AlterTable alias table schema # min :: AlterTable alias table schema -> AlterTable alias table schema -> AlterTable alias table schema # | |
Show (AlterTable alias table schema) Source # | |
Defined in Squeal.PostgreSQL.Definition Methods showsPrec :: Int -> AlterTable alias table schema -> ShowS # show :: AlterTable alias table schema -> String # showList :: [AlterTable alias table schema] -> ShowS # | |
Generic (AlterTable alias table schema) Source # | |
Defined in Squeal.PostgreSQL.Definition Associated Types type Rep (AlterTable alias table schema) :: * -> * # Methods from :: AlterTable alias table schema -> Rep (AlterTable alias table schema) x # to :: Rep (AlterTable alias table schema) x -> AlterTable alias table schema # | |
NFData (AlterTable alias table schema) Source # | |
Defined in Squeal.PostgreSQL.Definition Methods rnf :: AlterTable alias table schema -> () # | |
type Rep (AlterTable alias table schema) Source # | |
Defined in Squeal.PostgreSQL.Definition type Rep (AlterTable alias table schema) = D1 (MetaData "AlterTable" "Squeal.PostgreSQL.Definition" "squeal-postgresql-0.3.1.0-DNDeh0HTANH3vXYqblRMwD" True) (C1 (MetaCons "UnsafeAlterTable" PrefixI True) (S1 (MetaSel (Just "renderAlterTable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString))) |
Arguments
:: (KnownSymbol alias, Has tab schema (Table table0), table0 ~ (constraints :=> columns), table1 ~ (Create alias constraint constraints :=> columns)) | |
=> Alias alias | |
-> TableConstraintExpression schema tab constraint | constraint to add |
-> AlterTable tab table1 schema |
An addConstraint
adds a table constraint.
>>>
:{
let definition :: Definition '["tab" ::: 'Table ('[] :=> '["col" ::: 'NoDef :=> 'NotNull 'PGint4])] '["tab" ::: 'Table ('["positive" ::: Check '["col"]] :=> '["col" ::: 'NoDef :=> 'NotNull 'PGint4])] definition = alterTable #tab (addConstraint #positive (check #col (#col .> 0))) in printSQL definition :} ALTER TABLE "tab" ADD CONSTRAINT "positive" CHECK (("col" > 0));
Arguments
:: (KnownSymbol constraint, Has tab schema (Table table0), table0 ~ (constraints :=> columns), table1 ~ (Drop constraint constraints :=> columns)) | |
=> Alias constraint | constraint to drop |
-> AlterTable tab table1 schema |
A dropConstraint
drops a table constraint.
>>>
:{
let definition :: Definition '["tab" ::: 'Table ('["positive" ::: Check '["col"]] :=> '["col" ::: 'NoDef :=> 'NotNull 'PGint4])] '["tab" ::: 'Table ('[] :=> '["col" ::: 'NoDef :=> 'NotNull 'PGint4])] definition = alterTable #tab (dropConstraint #positive) in printSQL definition :} ALTER TABLE "tab" DROP CONSTRAINT "positive";
class AddColumn ty where Source #
An AddColumn
is either NULL
or has DEFAULT
.
Methods
Arguments
:: (KnownSymbol column, Has tab schema (Table table0), table0 ~ (constraints :=> columns), table1 ~ (constraints :=> Create column ty columns)) | |
=> Alias column | column to add |
-> ColumnTypeExpression schema ty | type of the new column |
-> AlterTable tab table1 schema |
addColumn
adds a new column, initially filled with whatever
default value is given or with NULL
.
>>>
:{
let definition :: Definition '["tab" ::: 'Table ('[] :=> '["col1" ::: 'NoDef :=> 'Null 'PGint4])] '["tab" ::: 'Table ('[] :=> '[ "col1" ::: 'NoDef :=> 'Null 'PGint4 , "col2" ::: 'Def :=> 'Null 'PGtext ])] definition = alterTable #tab (addColumn #col2 (text & nullable & default_ "foo")) in printSQL definition :} ALTER TABLE "tab" ADD COLUMN "col2" text NULL DEFAULT E'foo';
>>>
:{
let definition :: Definition '["tab" ::: 'Table ('[] :=> '["col1" ::: 'NoDef :=> 'Null 'PGint4])] '["tab" ::: 'Table ('[] :=> '[ "col1" ::: 'NoDef :=> 'Null 'PGint4 , "col2" ::: 'NoDef :=> 'Null 'PGtext ])] definition = alterTable #tab (addColumn #col2 (text & nullable)) in printSQL definition :} ALTER TABLE "tab" ADD COLUMN "col2" text NULL;
Arguments
:: (KnownSymbol column, Has tab schema (Table table0), table0 ~ (constraints :=> columns), table1 ~ (constraints :=> Drop column columns)) | |
=> Alias column | column to remove |
-> AlterTable tab table1 schema |
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" ::: 'Table ('[] :=> '[ "col1" ::: 'NoDef :=> 'Null 'PGint4 , "col2" ::: 'NoDef :=> 'Null 'PGtext ])] '["tab" ::: 'Table ('[] :=> '["col1" ::: 'NoDef :=> 'Null 'PGint4])] definition = alterTable #tab (dropColumn #col2) in printSQL definition :} ALTER TABLE "tab" DROP COLUMN "col2";
Arguments
:: (KnownSymbol column0, KnownSymbol column1, Has tab schema (Table table0), table0 ~ (constraints :=> columns), table1 ~ (constraints :=> Rename column0 column1 columns)) | |
=> Alias column0 | column to rename |
-> Alias column1 | what to rename the column |
-> AlterTable tab table1 schema |
A renameColumn
renames a column.
>>>
:{
let definition :: Definition '["tab" ::: 'Table ('[] :=> '["foo" ::: 'NoDef :=> 'Null 'PGint4])] '["tab" ::: 'Table ('[] :=> '["bar" ::: 'NoDef :=> 'Null 'PGint4])] definition = alterTable #tab (renameColumn #foo #bar) in printSQL definition :} ALTER TABLE "tab" RENAME COLUMN "foo" TO "bar";
Arguments
:: (KnownSymbol column, Has tab schema (Table table0), table0 ~ (constraints :=> columns), Has column columns ty0, tables1 ~ (constraints :=> Alter column ty1 columns)) | |
=> Alias column | column to alter |
-> AlterColumn schema ty0 ty1 | alteration to perform |
-> AlterTable tab table1 schema |
An alterColumn
alters a single column.
newtype AlterColumn (schema :: SchemaType) (ty0 :: ColumnType) (ty1 :: ColumnType) Source #
An AlterColumn
describes the alteration to perform on a single column.
Constructors
UnsafeAlterColumn | |
Fields |
Instances
Eq (AlterColumn schema ty0 ty1) Source # | |
Defined in Squeal.PostgreSQL.Definition Methods (==) :: AlterColumn schema ty0 ty1 -> AlterColumn schema ty0 ty1 -> Bool # (/=) :: AlterColumn schema ty0 ty1 -> AlterColumn schema ty0 ty1 -> Bool # | |
Ord (AlterColumn schema ty0 ty1) Source # | |
Defined in Squeal.PostgreSQL.Definition Methods compare :: AlterColumn schema ty0 ty1 -> AlterColumn schema ty0 ty1 -> Ordering # (<) :: AlterColumn schema ty0 ty1 -> AlterColumn schema ty0 ty1 -> Bool # (<=) :: AlterColumn schema ty0 ty1 -> AlterColumn schema ty0 ty1 -> Bool # (>) :: AlterColumn schema ty0 ty1 -> AlterColumn schema ty0 ty1 -> Bool # (>=) :: AlterColumn schema ty0 ty1 -> AlterColumn schema ty0 ty1 -> Bool # max :: AlterColumn schema ty0 ty1 -> AlterColumn schema ty0 ty1 -> AlterColumn schema ty0 ty1 # min :: AlterColumn schema ty0 ty1 -> AlterColumn schema ty0 ty1 -> AlterColumn schema ty0 ty1 # | |
Show (AlterColumn schema ty0 ty1) Source # | |
Defined in Squeal.PostgreSQL.Definition Methods showsPrec :: Int -> AlterColumn schema ty0 ty1 -> ShowS # show :: AlterColumn schema ty0 ty1 -> String # showList :: [AlterColumn schema ty0 ty1] -> ShowS # | |
Generic (AlterColumn schema ty0 ty1) Source # | |
Defined in Squeal.PostgreSQL.Definition Associated Types type Rep (AlterColumn schema ty0 ty1) :: * -> * # Methods from :: AlterColumn schema ty0 ty1 -> Rep (AlterColumn schema ty0 ty1) x # to :: Rep (AlterColumn schema ty0 ty1) x -> AlterColumn schema ty0 ty1 # | |
NFData (AlterColumn schema ty0 ty1) Source # | |
Defined in Squeal.PostgreSQL.Definition Methods rnf :: AlterColumn schema ty0 ty1 -> () # | |
type Rep (AlterColumn schema ty0 ty1) Source # | |
Defined in Squeal.PostgreSQL.Definition type Rep (AlterColumn schema ty0 ty1) = D1 (MetaData "AlterColumn" "Squeal.PostgreSQL.Definition" "squeal-postgresql-0.3.1.0-DNDeh0HTANH3vXYqblRMwD" True) (C1 (MetaCons "UnsafeAlterColumn" PrefixI True) (S1 (MetaSel (Just "renderAlterColumn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString))) |
Arguments
:: Expression schema '[] Ungrouped '[] ty | default value to set |
-> AlterColumn schema (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" ::: 'Table ('[] :=> '["col" ::: 'NoDef :=> 'Null 'PGint4])] '["tab" ::: 'Table ('[] :=> '["col" ::: 'Def :=> 'Null 'PGint4])] definition = alterTable #tab (alterColumn #col (setDefault 5)) in printSQL definition :} ALTER TABLE "tab" ALTER COLUMN "col" SET DEFAULT 5;
dropDefault :: AlterColumn schema (Def :=> ty) (NoDef :=> ty) Source #
A dropDefault
removes any default value for a column.
>>>
:{
let definition :: Definition '["tab" ::: 'Table ('[] :=> '["col" ::: 'Def :=> 'Null 'PGint4])] '["tab" ::: 'Table ('[] :=> '["col" ::: 'NoDef :=> 'Null 'PGint4])] definition = alterTable #tab (alterColumn #col dropDefault) in printSQL definition :} ALTER TABLE "tab" ALTER COLUMN "col" DROP DEFAULT;
setNotNull :: AlterColumn schema (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" ::: 'Table ('[] :=> '["col" ::: 'NoDef :=> 'Null 'PGint4])] '["tab" ::: 'Table ('[] :=> '["col" ::: 'NoDef :=> 'NotNull 'PGint4])] definition = alterTable #tab (alterColumn #col setNotNull) in printSQL definition :} ALTER TABLE "tab" ALTER COLUMN "col" SET NOT NULL;
dropNotNull :: AlterColumn schema (constraint :=> NotNull ty) (constraint :=> Null ty) Source #
A dropNotNull
drops a NOT NULL
constraint from a column.
>>>
:{
let definition :: Definition '["tab" ::: 'Table ('[] :=> '["col" ::: 'NoDef :=> 'NotNull 'PGint4])] '["tab" ::: 'Table ('[] :=> '["col" ::: 'NoDef :=> 'Null 'PGint4])] definition = alterTable #tab (alterColumn #col dropNotNull) in printSQL definition :} ALTER TABLE "tab" ALTER COLUMN "col" DROP NOT NULL;
alterType :: ColumnTypeExpression schema ty -> AlterColumn schema 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" ::: 'Table ('[] :=> '["col" ::: 'NoDef :=> 'NotNull 'PGint4])] '["tab" ::: 'Table ('[] :=> '["col" ::: 'NoDef :=> 'NotNull 'PGnumeric])] definition = alterTable #tab (alterColumn #col (alterType (numeric & notNullable))) in printSQL definition :} ALTER TABLE "tab" ALTER COLUMN "col" TYPE numeric NOT NULL;
Views
Arguments
:: KnownSymbol view | |
=> Alias view | the name of the view to add |
-> Query schema '[] relation | query |
-> Definition schema (Create view (View relation) schema) |
Create a view.
>>>
:{
let definition :: Definition '[ "abc" ::: 'Table ('[] :=> '["a" ::: 'NoDef :=> 'Null 'PGint4, "b" ::: 'NoDef :=> 'Null 'PGint4, "c" ::: 'NoDef :=> 'Null 'PGint4])] '[ "abc" ::: 'Table ('[] :=> '["a" ::: 'NoDef :=> 'Null 'PGint4, "b" ::: 'NoDef :=> 'Null 'PGint4, "c" ::: 'NoDef :=> 'Null 'PGint4]) , "bc" ::: 'View ('["b" ::: 'Null 'PGint4, "c" ::: 'Null 'PGint4])] definition = createView #bc (select (#b :* #c) (from (table #abc))) in printSQL definition :} CREATE VIEW "bc" AS SELECT "b" AS "b", "c" AS "c" FROM "abc" AS "abc";
Arguments
:: Has view schema (View v) | |
=> Alias view | view to remove |
-> Definition schema (Drop view schema) |
Drop a view.
>>>
:{
let definition :: Definition '[ "abc" ::: 'Table ('[] :=> '["a" ::: 'NoDef :=> 'Null 'PGint4, "b" ::: 'NoDef :=> 'Null 'PGint4, "c" ::: 'NoDef :=> 'Null 'PGint4]) , "bc" ::: 'View ('["b" ::: 'Null 'PGint4, "c" ::: 'Null 'PGint4])] '[ "abc" ::: 'Table ('[] :=> '["a" ::: 'NoDef :=> 'Null 'PGint4, "b" ::: 'NoDef :=> 'Null 'PGint4, "c" ::: 'NoDef :=> 'Null 'PGint4])] definition = dropView #bc in printSQL definition :} DROP VIEW "bc";
Types
Arguments
:: (KnownSymbol enum, All KnownSymbol labels) | |
=> Alias enum | name of the user defined enumerated type |
-> NP PGlabel labels | labels of the enumerated type |
-> Definition schema (Create enum (Typedef (PGenum labels)) schema) |
Enumerated types are created using the createTypeEnum
command, for example
>>>
printSQL $ createTypeEnum #mood (label @"sad" :* label @"ok" :* label @"happy")
CREATE TYPE "mood" AS ENUM ('sad', 'ok', 'happy');
Arguments
:: (Generic hask, All KnownSymbol (LabelsFrom hask), KnownSymbol enum) | |
=> Alias enum | name of the user defined enumerated type |
-> Definition schema (Create enum (Typedef (EnumFrom hask)) schema) |
Enumerated types can also be generated from a Haskell type, for example
>>>
data Schwarma = Beef | Lamb | Chicken deriving GHC.Generic
>>>
instance SOP.Generic Schwarma
>>>
instance SOP.HasDatatypeInfo Schwarma
>>>
printSQL $ createTypeEnumFrom @Schwarma #schwarma
CREATE TYPE "schwarma" AS ENUM ('Beef', 'Lamb', 'Chicken');
Arguments
:: (KnownSymbol ty, SListI fields) | |
=> Alias ty | name of the user defined composite type |
-> NP (Aliased (TypeExpression schema)) fields | list of attribute names and data types |
-> Definition schema (Create ty (Typedef (PGcomposite fields)) schema) |
createTypeComposite
creates a composite type. The composite type is
specified by a list of attribute names and data types.
>>>
type PGcomplex = 'PGcomposite '["real" ::: 'PGfloat8, "imaginary" ::: 'PGfloat8]
>>>
:{
let setup :: Definition '[] '["complex" ::: 'Typedef PGcomplex] setup = createTypeComposite #complex (float8 `as` #real :* float8 `as` #imaginary) in printSQL setup :} CREATE TYPE "complex" AS ("real" float8, "imaginary" float8);
createTypeCompositeFrom Source #
Arguments
:: (ZipAliased (FieldNamesFrom hask) (FieldTypesFrom hask), All (PGTyped schema) (FieldTypesFrom hask), KnownSymbol ty) | |
=> Alias ty | name of the user defined composite type |
-> Definition schema (Create ty (Typedef (CompositeFrom hask)) schema) |
Composite types can also be generated from a Haskell type, for example
>>>
data Complex = Complex {real :: Maybe Double, imaginary :: Maybe Double} deriving GHC.Generic
>>>
instance SOP.Generic Complex
>>>
instance SOP.HasDatatypeInfo Complex
>>>
printSQL $ createTypeCompositeFrom @Complex #complex
CREATE TYPE "complex" AS ("real" float8, "imaginary" float8);
Arguments
:: Has tydef schema (Typedef ty) | |
=> Alias tydef | name of the user defined type |
-> Definition schema (Drop tydef schema) |
Drop a type.
>>>
data Schwarma = Beef | Lamb | Chicken deriving GHC.Generic
>>>
instance SOP.Generic Schwarma
>>>
instance SOP.HasDatatypeInfo Schwarma
>>>
printSQL (dropType #schwarma :: Definition '["schwarma" ::: 'Typedef (EnumFrom Schwarma)] '[])
DROP TYPE "schwarma";
Columns
newtype ColumnTypeExpression (schema :: SchemaType) (ty :: ColumnType) Source #
ColumnTypeExpression
s are used in createTable
commands.
Constructors
UnsafeColumnTypeExpression | |
Fields |
Instances
nullable :: TypeExpression schema ty -> ColumnTypeExpression schema (NoDef :=> Null ty) Source #
used in createTable
commands as a column constraint to note that
NULL
may be present in a column
notNullable :: TypeExpression schema ty -> ColumnTypeExpression schema (def :=> NotNull ty) Source #
used in createTable
commands as a column constraint to ensure
NULL
is not present in a column
default_ :: Expression schema '[] Ungrouped '[] ty -> ColumnTypeExpression schema (NoDef :=> ty) -> ColumnTypeExpression schema (Def :=> ty) Source #
used in createTable
commands as a column constraint to give a default
serial2 :: ColumnTypeExpression schema (Def :=> NotNull PGint2) Source #
not a true type, but merely a notational convenience for creating
unique identifier columns with type PGint2
smallserial :: ColumnTypeExpression schema (Def :=> NotNull PGint2) Source #
not a true type, but merely a notational convenience for creating
unique identifier columns with type PGint2
serial4 :: ColumnTypeExpression schema (Def :=> NotNull PGint4) Source #
not a true type, but merely a notational convenience for creating
unique identifier columns with type PGint4
serial :: ColumnTypeExpression schema (Def :=> NotNull PGint4) Source #
not a true type, but merely a notational convenience for creating
unique identifier columns with type PGint4