squeal-postgresql-0.2.1.0: Squeal PostgreSQL Library

Copyright(c) Eitan Chatav 2017
Maintainereitan@morphism.tech
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Squeal.PostgreSQL.Definition

Contents

Description

Squeal data definition language.

Synopsis

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.

Instances

Category TablesType Definition Source # 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

Eq (Definition schema0 schema1) Source # 

Methods

(==) :: Definition schema0 schema1 -> Definition schema0 schema1 -> Bool #

(/=) :: Definition schema0 schema1 -> Definition schema0 schema1 -> Bool #

Ord (Definition schema0 schema1) Source # 

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 # 

Methods

showsPrec :: Int -> Definition schema0 schema1 -> ShowS #

show :: Definition schema0 schema1 -> String #

showList :: [Definition schema0 schema1] -> ShowS #

Generic (Definition schema0 schema1) Source # 

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 # 

Methods

rnf :: Definition schema0 schema1 -> () #

type Rep (Definition schema0 schema1) Source # 
type Rep (Definition schema0 schema1) = D1 * (MetaData "Definition" "Squeal.PostgreSQL.Definition" "squeal-postgresql-0.2.1.0-LBCcz8qiN2YKV8JaWeUPNP" True) (C1 * (MetaCons "UnsafeDefinition" PrefixI True) (S1 * (MetaSel (Just Symbol "renderDefinition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ByteString)))

(>>>) :: Category k cat => cat a b -> cat b c -> cat a c infixr 1 #

Left-to-right composition

Create

createTable Source #

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.

Instances

Eq (TableConstraintExpression schema columns tableConstraint) Source # 

Methods

(==) :: TableConstraintExpression schema columns tableConstraint -> TableConstraintExpression schema columns tableConstraint -> Bool #

(/=) :: TableConstraintExpression schema columns tableConstraint -> TableConstraintExpression schema columns tableConstraint -> Bool #

Ord (TableConstraintExpression schema columns tableConstraint) Source # 

Methods

compare :: TableConstraintExpression schema columns tableConstraint -> TableConstraintExpression schema columns tableConstraint -> Ordering #

(<) :: TableConstraintExpression schema columns tableConstraint -> TableConstraintExpression schema columns tableConstraint -> Bool #

(<=) :: TableConstraintExpression schema columns tableConstraint -> TableConstraintExpression schema columns tableConstraint -> Bool #

(>) :: TableConstraintExpression schema columns tableConstraint -> TableConstraintExpression schema columns tableConstraint -> Bool #

(>=) :: TableConstraintExpression schema columns tableConstraint -> TableConstraintExpression schema columns tableConstraint -> Bool #

max :: TableConstraintExpression schema columns tableConstraint -> TableConstraintExpression schema columns tableConstraint -> TableConstraintExpression schema columns tableConstraint #

min :: TableConstraintExpression schema columns tableConstraint -> TableConstraintExpression schema columns tableConstraint -> TableConstraintExpression schema columns tableConstraint #

Show (TableConstraintExpression schema columns tableConstraint) Source # 

Methods

showsPrec :: Int -> TableConstraintExpression schema columns tableConstraint -> ShowS #

show :: TableConstraintExpression schema columns tableConstraint -> String #

showList :: [TableConstraintExpression schema columns tableConstraint] -> ShowS #

Generic (TableConstraintExpression schema columns tableConstraint) Source # 

Associated Types

type Rep (TableConstraintExpression schema columns tableConstraint) :: * -> * #

Methods

from :: TableConstraintExpression schema columns tableConstraint -> Rep (TableConstraintExpression schema columns tableConstraint) x #

to :: Rep (TableConstraintExpression schema columns tableConstraint) x -> TableConstraintExpression schema columns tableConstraint #

NFData (TableConstraintExpression schema columns tableConstraint) Source # 

Methods

rnf :: TableConstraintExpression schema columns tableConstraint -> () #

type Rep (TableConstraintExpression schema columns tableConstraint) Source # 
type Rep (TableConstraintExpression schema columns tableConstraint) = D1 * (MetaData "TableConstraintExpression" "Squeal.PostgreSQL.Definition" "squeal-postgresql-0.2.1.0-LBCcz8qiN2YKV8JaWeUPNP" True) (C1 * (MetaCons "UnsafeTableConstraintExpression" PrefixI True) (S1 * (MetaSel (Just Symbol "renderTableConstraintExpression") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ByteString)))

data Column (columns :: ColumnsType) (column :: (Symbol, ColumnType)) where Source #

Column columns column is a witness that column is in columns.

Constructors

Column :: Has column columns ty => Alias column -> Column columns (column ::: ty) 

check Source #

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\")));"

unique Source #

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\"));"

primaryKey Source #

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\"));"

foreignKey Source #

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

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)

Drop

dropTable Source #

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

alterTable Source #

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.

alterTableRename Source #

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.

Instances

Eq (AlterTable schema table0 table1) Source # 

Methods

(==) :: AlterTable schema table0 table1 -> AlterTable schema table0 table1 -> Bool #

(/=) :: AlterTable schema table0 table1 -> AlterTable schema table0 table1 -> Bool #

Ord (AlterTable schema table0 table1) Source # 

Methods

compare :: AlterTable schema table0 table1 -> AlterTable schema table0 table1 -> Ordering #

(<) :: AlterTable schema table0 table1 -> AlterTable schema table0 table1 -> Bool #

(<=) :: AlterTable schema table0 table1 -> AlterTable schema table0 table1 -> Bool #

(>) :: AlterTable schema table0 table1 -> AlterTable schema table0 table1 -> Bool #

(>=) :: AlterTable schema table0 table1 -> AlterTable schema table0 table1 -> Bool #

max :: AlterTable schema table0 table1 -> AlterTable schema table0 table1 -> AlterTable schema table0 table1 #

min :: AlterTable schema table0 table1 -> AlterTable schema table0 table1 -> AlterTable schema table0 table1 #

Show (AlterTable schema table0 table1) Source # 

Methods

showsPrec :: Int -> AlterTable schema table0 table1 -> ShowS #

show :: AlterTable schema table0 table1 -> String #

showList :: [AlterTable schema table0 table1] -> ShowS #

Generic (AlterTable schema table0 table1) Source # 

Associated Types

type Rep (AlterTable schema table0 table1) :: * -> * #

Methods

from :: AlterTable schema table0 table1 -> Rep (AlterTable schema table0 table1) x #

to :: Rep (AlterTable schema table0 table1) x -> AlterTable schema table0 table1 #

NFData (AlterTable schema table0 table1) Source # 

Methods

rnf :: AlterTable schema table0 table1 -> () #

type Rep (AlterTable schema table0 table1) Source # 
type Rep (AlterTable schema table0 table1) = D1 * (MetaData "AlterTable" "Squeal.PostgreSQL.Definition" "squeal-postgresql-0.2.1.0-LBCcz8qiN2YKV8JaWeUPNP" True) (C1 * (MetaCons "UnsafeAlterTable" PrefixI True) (S1 * (MetaSel (Just Symbol "renderAlterTable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ByteString)))

addConstraint 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));"

dropConstraint Source #

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

addColumn Source #

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;"

dropColumn Source #

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\";"

renameColumn Source #

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\";"

alterColumn Source #

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.

Instances

Eq (AlterColumn ty0 ty1) Source # 

Methods

(==) :: AlterColumn ty0 ty1 -> AlterColumn ty0 ty1 -> Bool #

(/=) :: AlterColumn ty0 ty1 -> AlterColumn ty0 ty1 -> Bool #

Ord (AlterColumn ty0 ty1) Source # 

Methods

compare :: AlterColumn ty0 ty1 -> AlterColumn ty0 ty1 -> Ordering #

(<) :: AlterColumn ty0 ty1 -> AlterColumn ty0 ty1 -> Bool #

(<=) :: AlterColumn ty0 ty1 -> AlterColumn ty0 ty1 -> Bool #

(>) :: AlterColumn ty0 ty1 -> AlterColumn ty0 ty1 -> Bool #

(>=) :: AlterColumn ty0 ty1 -> AlterColumn ty0 ty1 -> Bool #

max :: AlterColumn ty0 ty1 -> AlterColumn ty0 ty1 -> AlterColumn ty0 ty1 #

min :: AlterColumn ty0 ty1 -> AlterColumn ty0 ty1 -> AlterColumn ty0 ty1 #

Show (AlterColumn ty0 ty1) Source # 

Methods

showsPrec :: Int -> AlterColumn ty0 ty1 -> ShowS #

show :: AlterColumn ty0 ty1 -> String #

showList :: [AlterColumn ty0 ty1] -> ShowS #

Generic (AlterColumn ty0 ty1) Source # 

Associated Types

type Rep (AlterColumn ty0 ty1) :: * -> * #

Methods

from :: AlterColumn ty0 ty1 -> Rep (AlterColumn ty0 ty1) x #

to :: Rep (AlterColumn ty0 ty1) x -> AlterColumn ty0 ty1 #

NFData (AlterColumn ty0 ty1) Source # 

Methods

rnf :: AlterColumn ty0 ty1 -> () #

type Rep (AlterColumn ty0 ty1) Source # 
type Rep (AlterColumn ty0 ty1) = D1 * (MetaData "AlterColumn" "Squeal.PostgreSQL.Definition" "squeal-postgresql-0.2.1.0-LBCcz8qiN2YKV8JaWeUPNP" True) (C1 * (MetaCons "UnsafeAlterColumn" PrefixI True) (S1 * (MetaSel (Just Symbol "renderAlterColumn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ByteString)))

setDefault 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;"