squeal-postgresql-0.7.0.1: Squeal PostgreSQL Library

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

Squeal.PostgreSQL.Definition.Constraint

Contents

Description

constraint expressions

Synopsis

Table Constraints

newtype TableConstraintExpression (sch :: Symbol) (tab :: Symbol) (db :: SchemasType) (constraint :: 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 sch tab db constraint) Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

Methods

(==) :: TableConstraintExpression sch tab db constraint -> TableConstraintExpression sch tab db constraint -> Bool #

(/=) :: TableConstraintExpression sch tab db constraint -> TableConstraintExpression sch tab db constraint -> Bool #

Ord (TableConstraintExpression sch tab db constraint) Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

Methods

compare :: TableConstraintExpression sch tab db constraint -> TableConstraintExpression sch tab db constraint -> Ordering #

(<) :: TableConstraintExpression sch tab db constraint -> TableConstraintExpression sch tab db constraint -> Bool #

(<=) :: TableConstraintExpression sch tab db constraint -> TableConstraintExpression sch tab db constraint -> Bool #

(>) :: TableConstraintExpression sch tab db constraint -> TableConstraintExpression sch tab db constraint -> Bool #

(>=) :: TableConstraintExpression sch tab db constraint -> TableConstraintExpression sch tab db constraint -> Bool #

max :: TableConstraintExpression sch tab db constraint -> TableConstraintExpression sch tab db constraint -> TableConstraintExpression sch tab db constraint #

min :: TableConstraintExpression sch tab db constraint -> TableConstraintExpression sch tab db constraint -> TableConstraintExpression sch tab db constraint #

Show (TableConstraintExpression sch tab db constraint) Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

Methods

showsPrec :: Int -> TableConstraintExpression sch tab db constraint -> ShowS #

show :: TableConstraintExpression sch tab db constraint -> String #

showList :: [TableConstraintExpression sch tab db constraint] -> ShowS #

Generic (TableConstraintExpression sch tab db constraint) Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

Associated Types

type Rep (TableConstraintExpression sch tab db constraint) :: Type -> Type #

Methods

from :: TableConstraintExpression sch tab db constraint -> Rep (TableConstraintExpression sch tab db constraint) x #

to :: Rep (TableConstraintExpression sch tab db constraint) x -> TableConstraintExpression sch tab db constraint #

NFData (TableConstraintExpression sch tab db constraint) Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

Methods

rnf :: TableConstraintExpression sch tab db constraint -> () #

RenderSQL (TableConstraintExpression sch tab db constraint) Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

Methods

renderSQL :: TableConstraintExpression sch tab db constraint -> ByteString Source #

type Rep (TableConstraintExpression sch tab db constraint) Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

type Rep (TableConstraintExpression sch tab db constraint) = D1 (MetaData "TableConstraintExpression" "Squeal.PostgreSQL.Definition.Constraint" "squeal-postgresql-0.7.0.1-33cXMmdyUeW5J6FQU4gmil" True) (C1 (MetaCons "UnsafeTableConstraintExpression" PrefixI True) (S1 (MetaSel (Just "renderTableConstraintExpression") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)))

check Source #

Arguments

:: (Has sch db schema, Has tab schema (Table table), HasAll aliases (TableToRow table) subcolumns) 
=> NP Alias aliases

specify the subcolumns which are getting checked

-> (forall t. Condition Ungrouped '[] '[] db '[] '[t ::: subcolumns])

a closed Condition on those subcolumns

-> TableConstraintExpression sch tab db (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 (Public '[]) (Public 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")));

unique Source #

Arguments

:: (Has sch db schema, Has tab schema (Table table), HasAll aliases (TableToRow table) subcolumns) 
=> NP Alias aliases

specify subcolumns which together are unique for each row

-> TableConstraintExpression sch tab db (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 (Public '[]) (Public 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"));

primaryKey Source #

Arguments

:: (Has sch db schema, Has tab schema (Table table), HasAll aliases (TableToColumns table) subcolumns, AllNotNull subcolumns) 
=> NP Alias aliases

specify the subcolumns which together form a primary key.

-> TableConstraintExpression sch tab db (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 (Public '[]) (Public 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"));

Foreign Keys

foreignKey Source #

Arguments

:: ForeignKeyed db sch0 sch1 schema0 schema1 child parent table reftable columns refcolumns constraints cols reftys tys 
=> NP Alias columns

column or columns in the table

-> QualifiedAlias sch0 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 sch1 child db (ForeignKey columns sch0 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"] "public" "users" '["id"]
        ] :=>
       '[ "id" ::: 'Def :=> 'NotNull 'PGint4
        , "user_id" ::: 'NoDef :=> 'NotNull 'PGint4
        , "email" ::: 'NoDef :=> 'Null 'PGtext
        ])
   ]
:}
>>> :{
let
  setup :: Definition (Public '[]) (Public 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
         (OnDelete Cascade) (OnUpdate Cascade) `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"] "public" "employees" '["id"]
        ] :=>
       '[ "id"          :::   'Def :=> 'NotNull 'PGint4
        , "name"        ::: 'NoDef :=> 'NotNull 'PGtext
        , "employer_id" ::: 'NoDef :=>    'Null 'PGint4
        ])
   ]
:}
>>> :{
let
  setup :: Definition (Public '[]) (Public 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
         (OnDelete Cascade) (OnUpdate Cascade) `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 db sch0 sch1 schema0 schema1 child parent table reftable columns refcolumns constraints cols reftys tys = (Has sch0 db schema0, Has sch1 db schema1, Has parent schema0 (Table reftable), Has child schema1 (Table table), 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.

newtype OnDeleteClause Source #

OnDeleteClause indicates what to do with rows that reference a deleted row.

Instances
Eq OnDeleteClause Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

Ord OnDeleteClause Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

Show OnDeleteClause Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

Generic OnDeleteClause Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

Associated Types

type Rep OnDeleteClause :: Type -> Type #

NFData OnDeleteClause Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

Methods

rnf :: OnDeleteClause -> () #

RenderSQL OnDeleteClause Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

type Rep OnDeleteClause Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

type Rep OnDeleteClause = D1 (MetaData "OnDeleteClause" "Squeal.PostgreSQL.Definition.Constraint" "squeal-postgresql-0.7.0.1-33cXMmdyUeW5J6FQU4gmil" True) (C1 (MetaCons "OnDelete" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ReferentialAction)))

newtype OnUpdateClause Source #

Analagous to OnDeleteClause there is also OnUpdateClause which is invoked when a referenced column is changed (updated).

Instances
Eq OnUpdateClause Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

Ord OnUpdateClause Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

Show OnUpdateClause Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

Generic OnUpdateClause Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

Associated Types

type Rep OnUpdateClause :: Type -> Type #

NFData OnUpdateClause Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

Methods

rnf :: OnUpdateClause -> () #

RenderSQL OnUpdateClause Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

type Rep OnUpdateClause Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

type Rep OnUpdateClause = D1 (MetaData "OnUpdateClause" "Squeal.PostgreSQL.Definition.Constraint" "squeal-postgresql-0.7.0.1-33cXMmdyUeW5J6FQU4gmil" True) (C1 (MetaCons "OnUpdate" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ReferentialAction)))

data ReferentialAction Source #

When the data in the referenced columns is changed, certain actions are performed on the data in this table's columns.

Constructors

NoAction

Produce an error indicating that the deletion or update would create a foreign key constraint violation. If the constraint is deferred, this error will be produced at constraint check time if there still exist any referencing rows.

Restrict

Produce an error indicating that the deletion or update would create a foreign key constraint violation. This is the same as NoAction except that the check is not deferrable.

Cascade

Delete any rows referencing the deleted row, or update the value of the referencing column to the new value of the referenced column, respectively.

SetNull

Set the referencing column(s) to null.

SetDefault

Set the referencing column(s) to their default values.

Instances
Eq ReferentialAction Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

Ord ReferentialAction Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

Show ReferentialAction Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

Generic ReferentialAction Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

Associated Types

type Rep ReferentialAction :: Type -> Type #

NFData ReferentialAction Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

Methods

rnf :: ReferentialAction -> () #

RenderSQL ReferentialAction Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

type Rep ReferentialAction Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

type Rep ReferentialAction = D1 (MetaData "ReferentialAction" "Squeal.PostgreSQL.Definition.Constraint" "squeal-postgresql-0.7.0.1-33cXMmdyUeW5J6FQU4gmil" False) ((C1 (MetaCons "NoAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Restrict" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Cascade" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "SetNull" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SetDefault" PrefixI False) (U1 :: Type -> Type))))