Copyright | (c) Eitan Chatav 2019 |
---|---|
Maintainer | eitan@morphism.tech |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
create, drop and alter tables
Synopsis
- createTable :: (KnownSymbol sch, KnownSymbol tab, columns ~ (col ': cols), SListI columns, SListI constraints, Has sch db0 schema0, db1 ~ Alter sch (Create tab ('Table (constraints :=> columns)) schema0) db0) => QualifiedAlias sch tab -> NP (Aliased (ColumnTypeExpression db0)) columns -> NP (Aliased (TableConstraintExpression sch tab db1)) constraints -> Definition db0 db1
- createTableIfNotExists :: (KnownSymbol sch, KnownSymbol tab, columns ~ (col ': cols), SListI columns, SListI constraints, Has sch db0 schema0, db1 ~ Alter sch (CreateIfNotExists tab ('Table (constraints :=> columns)) schema0) db0) => QualifiedAlias sch tab -> NP (Aliased (ColumnTypeExpression db0)) columns -> NP (Aliased (TableConstraintExpression sch tab db1)) constraints -> Definition db0 db1
- dropTable :: (Has sch db schema, KnownSymbol tab) => QualifiedAlias sch tab -> Definition db (Alter sch (DropSchemum tab 'Table schema) db)
- dropTableIfExists :: (Has sch db schema, KnownSymbol tab) => QualifiedAlias sch tab -> Definition db (Alter sch (DropSchemumIfExists tab 'Table schema) db)
- alterTable :: (Has sch db schema, KnownSymbol tab) => QualifiedAlias sch tab -> AlterTable sch tab db table -> Definition db (Alter sch (Alter tab ('Table table) schema) db)
- alterTableIfExists :: (Has sch db schema, KnownSymbol tab) => QualifiedAlias sch tab -> AlterTable sch tab db table -> Definition db (Alter sch (AlterIfExists tab ('Table table) schema) db)
- alterTableRename :: (Has sch db schema, KnownSymbol tab1, Has tab0 schema ('Table table)) => QualifiedAlias sch tab0 -> Alias tab1 -> Definition db (Alter sch (Rename tab0 tab1 schema) db)
- alterTableIfExistsRename :: (Has sch db schema, KnownSymbol tab0, KnownSymbol tab1) => QualifiedAlias sch tab0 -> Alias tab1 -> Definition db (Alter sch (RenameIfExists tab0 tab1 schema) db)
- alterTableSetSchema :: (Has sch0 db schema0, Has tab schema0 ('Table table), Has sch1 db schema1) => QualifiedAlias sch0 tab -> Alias sch1 -> Definition db (SetSchema sch0 sch1 schema0 schema1 tab 'Table table db)
- newtype AlterTable (sch :: Symbol) (tab :: Symbol) (db :: SchemasType) (table :: TableType) = UnsafeAlterTable {}
- addConstraint :: (KnownSymbol alias, Has sch db schema, Has tab schema ('Table (constraints :=> columns))) => Alias alias -> TableConstraintExpression sch tab db constraint -> AlterTable sch tab db (Create alias constraint constraints :=> columns)
- dropConstraint :: (KnownSymbol constraint, Has sch db schema, Has tab schema ('Table (constraints :=> columns))) => Alias constraint -> AlterTable sch tab db (Drop constraint constraints :=> columns)
- class AddColumn ty where
- addColumn :: (KnownSymbol column, Has sch db schema, Has tab schema ('Table (constraints :=> columns))) => Alias column -> ColumnTypeExpression db ty -> AlterTable sch tab db (constraints :=> Create column ty columns)
- dropColumn :: (KnownSymbol column, Has sch db schema, Has tab schema ('Table (constraints :=> columns))) => Alias column -> AlterTable sch tab db (constraints :=> Drop column columns)
- renameColumn :: (KnownSymbol column0, KnownSymbol column1, Has sch db schema, Has tab schema ('Table (constraints :=> columns))) => Alias column0 -> Alias column1 -> AlterTable sch tab db (constraints :=> Rename column0 column1 columns)
- alterColumn :: (KnownSymbol column, Has sch db schema, Has tab schema ('Table (constraints :=> columns)), Has column columns ty0) => Alias column -> AlterColumn db ty0 ty1 -> AlterTable sch tab db (constraints :=> Alter column ty1 columns)
- newtype AlterColumn (db :: SchemasType) (ty0 :: ColumnType) (ty1 :: ColumnType) = UnsafeAlterColumn {}
- setDefault :: Expression 'Ungrouped '[] '[] db '[] '[] ty -> AlterColumn db (constraint :=> ty) ('Def :=> ty)
- dropDefault :: AlterColumn db ('Def :=> ty) ('NoDef :=> ty)
- setNotNull :: AlterColumn db (constraint :=> 'Null ty) (constraint :=> 'NotNull ty)
- dropNotNull :: AlterColumn db (constraint :=> 'NotNull ty) (constraint :=> 'Null ty)
- alterType :: ColumnTypeExpression db ty -> AlterColumn db ty0 ty
Create
:: (KnownSymbol sch, KnownSymbol tab, columns ~ (col ': cols), SListI columns, SListI constraints, Has sch db0 schema0, db1 ~ Alter sch (Create tab ('Table (constraints :=> columns)) schema0) db0) | |
=> QualifiedAlias sch tab | the name of the table to add |
-> NP (Aliased (ColumnTypeExpression db0)) columns | the names and datatype of each column |
-> NP (Aliased (TableConstraintExpression sch tab db1)) constraints | constraints that must hold for the table |
-> Definition db0 db1 |
createTable
adds a table to the schema.
>>>
:set -XOverloadedLabels
>>>
:{
type Table = '[] :=> '[ "a" ::: 'NoDef :=> 'Null 'PGint4 , "b" ::: 'NoDef :=> 'Null 'PGfloat4 ] :}
>>>
:{
let setup :: Definition (Public '[]) (Public '["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 #
:: (KnownSymbol sch, KnownSymbol tab, columns ~ (col ': cols), SListI columns, SListI constraints, Has sch db0 schema0, db1 ~ Alter sch (CreateIfNotExists tab ('Table (constraints :=> columns)) schema0) db0) | |
=> QualifiedAlias sch tab | the name of the table to add |
-> NP (Aliased (ColumnTypeExpression db0)) columns | the names and datatype of each column |
-> NP (Aliased (TableConstraintExpression sch tab db1)) constraints | constraints that must hold for the table |
-> Definition db0 db1 |
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 Schemas = Public '["tab" ::: 'Table Table]
>>>
:{
let setup :: Definition Schemas Schemas 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);
Drop
:: (Has sch db schema, KnownSymbol tab) | |
=> QualifiedAlias sch tab | table to remove |
-> Definition db (Alter sch (DropSchemum tab 'Table schema) db) |
dropTable
removes a table from the schema.
>>>
:{
let definition :: Definition '["public" ::: '["muh_table" ::: 'Table t]] (Public '[]) definition = dropTable #muh_table :}
>>>
printSQL definition
DROP TABLE "muh_table";
:: (Has sch db schema, KnownSymbol tab) | |
=> QualifiedAlias sch tab | table to remove |
-> Definition db (Alter sch (DropSchemumIfExists tab 'Table schema) db) |
Drop a table if it exists.
Alter
:: (Has sch db schema, KnownSymbol tab) | |
=> QualifiedAlias sch tab | table to alter |
-> AlterTable sch tab db table | alteration to perform |
-> Definition db (Alter sch (Alter tab ('Table table) schema) db) |
alterTable
changes the definition of a table from the schema.
:: (Has sch db schema, KnownSymbol tab) | |
=> QualifiedAlias sch tab | table to alter |
-> AlterTable sch tab db table | alteration to perform |
-> Definition db (Alter sch (AlterIfExists tab ('Table table) schema) db) |
alterTable
changes the definition of a table from the schema.
:: (Has sch db schema, KnownSymbol tab1, Has tab0 schema ('Table table)) | |
=> QualifiedAlias sch tab0 | table to rename |
-> Alias tab1 | what to rename it |
-> Definition db (Alter sch (Rename tab0 tab1 schema) db) |
alterTableRename
changes the name of a table from the schema.
>>>
type Schemas = '[ "public" ::: '[ "foo" ::: 'Table ('[] :=> '[]) ] ]
>>>
:{
let migration :: Definition Schemas '["public" ::: '["bar" ::: 'Table ('[] :=> '[]) ] ] migration = alterTableRename #foo #bar in printSQL migration :} ALTER TABLE "foo" RENAME TO "bar";
alterTableIfExistsRename Source #
:: (Has sch db schema, KnownSymbol tab0, KnownSymbol tab1) | |
=> QualifiedAlias sch tab0 | table to rename |
-> Alias tab1 | what to rename it |
-> Definition db (Alter sch (RenameIfExists tab0 tab1 schema) db) |
alterTableIfExistsRename
changes the name of a table from the schema if it exists.
>>>
type Schemas = '[ "public" ::: '[ "foo" ::: 'Table ('[] :=> '[]) ] ]
>>>
:{
let migration :: Definition Schemas Schemas migration = alterTableIfExistsRename #goo #gar in printSQL migration :} ALTER TABLE IF EXISTS "goo" RENAME TO "gar";
:: (Has sch0 db schema0, Has tab schema0 ('Table table), Has sch1 db schema1) | |
=> QualifiedAlias sch0 tab | table to move |
-> Alias sch1 | where to move it |
-> Definition db (SetSchema sch0 sch1 schema0 schema1 tab 'Table table db) |
This form moves the table into another schema.
>>>
type DB0 = '[ "sch0" ::: '[ "tab" ::: 'Table ('[] :=> '[]) ], "sch1" ::: '[] ]
>>>
type DB1 = '[ "sch0" ::: '[], "sch1" ::: '[ "tab" ::: 'Table ('[] :=> '[]) ] ]
>>>
:{
let def :: Definition DB0 DB1 def = alterTableSetSchema (#sch0 ! #tab) #sch1 in printSQL def :} ALTER TABLE "sch0"."tab" SET SCHEMA "sch1";
newtype AlterTable (sch :: Symbol) (tab :: Symbol) (db :: SchemasType) (table :: TableType) Source #
An AlterTable
describes the alteration to perform on the columns
of a table.
Instances
Eq (AlterTable sch tab db table) Source # | |
Defined in Squeal.PostgreSQL.Definition.Table (==) :: AlterTable sch tab db table -> AlterTable sch tab db table -> Bool # (/=) :: AlterTable sch tab db table -> AlterTable sch tab db table -> Bool # | |
Ord (AlterTable sch tab db table) Source # | |
Defined in Squeal.PostgreSQL.Definition.Table compare :: AlterTable sch tab db table -> AlterTable sch tab db table -> Ordering # (<) :: AlterTable sch tab db table -> AlterTable sch tab db table -> Bool # (<=) :: AlterTable sch tab db table -> AlterTable sch tab db table -> Bool # (>) :: AlterTable sch tab db table -> AlterTable sch tab db table -> Bool # (>=) :: AlterTable sch tab db table -> AlterTable sch tab db table -> Bool # max :: AlterTable sch tab db table -> AlterTable sch tab db table -> AlterTable sch tab db table # min :: AlterTable sch tab db table -> AlterTable sch tab db table -> AlterTable sch tab db table # | |
Show (AlterTable sch tab db table) Source # | |
Defined in Squeal.PostgreSQL.Definition.Table showsPrec :: Int -> AlterTable sch tab db table -> ShowS # show :: AlterTable sch tab db table -> String # showList :: [AlterTable sch tab db table] -> ShowS # | |
Generic (AlterTable sch tab db table) Source # | |
Defined in Squeal.PostgreSQL.Definition.Table type Rep (AlterTable sch tab db table) :: Type -> Type # from :: AlterTable sch tab db table -> Rep (AlterTable sch tab db table) x # to :: Rep (AlterTable sch tab db table) x -> AlterTable sch tab db table # | |
NFData (AlterTable sch tab db table) Source # | |
Defined in Squeal.PostgreSQL.Definition.Table rnf :: AlterTable sch tab db table -> () # | |
type Rep (AlterTable sch tab db table) Source # | |
Defined in Squeal.PostgreSQL.Definition.Table type Rep (AlterTable sch tab db table) = D1 ('MetaData "AlterTable" "Squeal.PostgreSQL.Definition.Table" "squeal-postgresql-0.9.0.0-D17NIjlcsGRAwJTaCTXyvM" 'True) (C1 ('MetaCons "UnsafeAlterTable" 'PrefixI 'True) (S1 ('MetaSel ('Just "renderAlterTable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) |
Constraints
:: (KnownSymbol alias, Has sch db schema, Has tab schema ('Table (constraints :=> columns))) | |
=> Alias alias | |
-> TableConstraintExpression sch tab db constraint | constraint to add |
-> AlterTable sch tab db (Create alias constraint constraints :=> columns) |
An addConstraint
adds a table constraint.
>>>
:{
let definition :: Definition '["public" ::: '["tab" ::: 'Table ('[] :=> '["col" ::: 'NoDef :=> 'NotNull 'PGint4])]] '["public" ::: '["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 :: int4)));
:: (KnownSymbol constraint, Has sch db schema, Has tab schema ('Table (constraints :=> columns))) | |
=> Alias constraint | constraint to drop |
-> AlterTable sch tab db (Drop constraint constraints :=> columns) |
A dropConstraint
drops a table constraint.
>>>
:{
let definition :: Definition '["public" ::: '["tab" ::: 'Table ('["positive" ::: Check '["col"]] :=> '["col" ::: 'NoDef :=> 'NotNull 'PGint4])]] '["public" ::: '["tab" ::: 'Table ('[] :=> '["col" ::: 'NoDef :=> 'NotNull 'PGint4])]] definition = alterTable #tab (dropConstraint #positive) in printSQL definition :} ALTER TABLE "tab" DROP CONSTRAINT "positive";
Columns
class AddColumn ty where Source #
An AddColumn
is either NULL
or has DEFAULT
.
Nothing
:: (KnownSymbol column, Has sch db schema, Has tab schema ('Table (constraints :=> columns))) | |
=> Alias column | column to add |
-> ColumnTypeExpression db ty | type of the new column |
-> AlterTable sch tab db (constraints :=> Create column ty columns) |
addColumn
adds a new column, initially filled with whatever
default value is given or with NULL
.
>>>
:{
let definition :: Definition '["public" ::: '["tab" ::: 'Table ('[] :=> '["col1" ::: 'NoDef :=> 'Null 'PGint4])]] '["public" ::: '["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' :: text);
>>>
:{
let definition :: Definition '["public" ::: '["tab" ::: 'Table ('[] :=> '["col1" ::: 'NoDef :=> 'Null 'PGint4])]] '["public" ::: '["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;
Instances
AddColumn ('Def :=> ty) Source # | |
Defined in Squeal.PostgreSQL.Definition.Table addColumn :: forall (column :: Symbol) (sch :: Symbol) (db :: [(Symbol, [(Symbol, SchemumType)])]) (schema :: [(Symbol, SchemumType)]) (tab :: Symbol) (constraints :: TableConstraints) (columns :: ColumnsType). (KnownSymbol column, Has sch db schema, Has tab schema ('Table (constraints :=> columns))) => Alias column -> ColumnTypeExpression db ('Def :=> ty) -> AlterTable sch tab db (constraints :=> Create column ('Def :=> ty) columns) Source # | |
AddColumn ('NoDef :=> 'Null ty) Source # | |
Defined in Squeal.PostgreSQL.Definition.Table addColumn :: forall (column :: Symbol) (sch :: Symbol) (db :: [(Symbol, [(Symbol, SchemumType)])]) (schema :: [(Symbol, SchemumType)]) (tab :: Symbol) (constraints :: TableConstraints) (columns :: ColumnsType). (KnownSymbol column, Has sch db schema, Has tab schema ('Table (constraints :=> columns))) => Alias column -> ColumnTypeExpression db ('NoDef :=> 'Null ty) -> AlterTable sch tab db (constraints :=> Create column ('NoDef :=> 'Null ty) columns) Source # |
:: (KnownSymbol column, Has sch db schema, Has tab schema ('Table (constraints :=> columns))) | |
=> Alias column | column to remove |
-> AlterTable sch tab db (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 '["public" ::: '["tab" ::: 'Table ('[] :=> '[ "col1" ::: 'NoDef :=> 'Null 'PGint4 , "col2" ::: 'NoDef :=> 'Null 'PGtext ])]] '["public" ::: '["tab" ::: 'Table ('[] :=> '["col1" ::: 'NoDef :=> 'Null 'PGint4])]] definition = alterTable #tab (dropColumn #col2) in printSQL definition :} ALTER TABLE "tab" DROP COLUMN "col2";
:: (KnownSymbol column0, KnownSymbol column1, Has sch db schema, Has tab schema ('Table (constraints :=> columns))) | |
=> Alias column0 | column to rename |
-> Alias column1 | what to rename the column |
-> AlterTable sch tab db (constraints :=> Rename column0 column1 columns) |
A renameColumn
renames a column.
>>>
:{
let definition :: Definition '["public" ::: '["tab" ::: 'Table ('[] :=> '["foo" ::: 'NoDef :=> 'Null 'PGint4])]] '["public" ::: '["tab" ::: 'Table ('[] :=> '["bar" ::: 'NoDef :=> 'Null 'PGint4])]] definition = alterTable #tab (renameColumn #foo #bar) in printSQL definition :} ALTER TABLE "tab" RENAME COLUMN "foo" TO "bar";
:: (KnownSymbol column, Has sch db schema, Has tab schema ('Table (constraints :=> columns)), Has column columns ty0) | |
=> Alias column | column to alter |
-> AlterColumn db ty0 ty1 | alteration to perform |
-> AlterTable sch tab db (constraints :=> Alter column ty1 columns) |
An alterColumn
alters a single column.
newtype AlterColumn (db :: SchemasType) (ty0 :: ColumnType) (ty1 :: ColumnType) Source #
An AlterColumn
describes the alteration to perform on a single column.
Instances
:: Expression 'Ungrouped '[] '[] db '[] '[] ty | default value to set |
-> AlterColumn db (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 '["public" ::: '["tab" ::: 'Table ('[] :=> '["col" ::: 'NoDef :=> 'Null 'PGint4])]] '["public" ::: '["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 :: int4);
dropDefault :: AlterColumn db ('Def :=> ty) ('NoDef :=> ty) Source #
A dropDefault
removes any default value for a column.
>>>
:{
let definition :: Definition '["public" ::: '["tab" ::: 'Table ('[] :=> '["col" ::: 'Def :=> 'Null 'PGint4])]] '["public" ::: '["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 db (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 '["public" ::: '["tab" ::: 'Table ('[] :=> '["col" ::: 'NoDef :=> 'Null 'PGint4])]] '["public" ::: '["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 db (constraint :=> 'NotNull ty) (constraint :=> 'Null ty) Source #
A dropNotNull
drops a NOT NULL
constraint from a column.
>>>
:{
let definition :: Definition '["public" ::: '["tab" ::: 'Table ('[] :=> '["col" ::: 'NoDef :=> 'NotNull 'PGint4])]] '["public" ::: '["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 db ty -> AlterColumn db 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 '["public" ::: '["tab" ::: 'Table ('[] :=> '["col" ::: 'NoDef :=> 'NotNull 'PGint4])]] '["public" ::: '["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;