squeal-postgresql-0.1.0.0: Squeal PostgreSQL Library

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

Squeal.PostgreSQL.Schema

Contents

Description

Embedding of PostgreSQL type and alias system

Synopsis

Kinds

data PGType Source #

PGType is the promoted datakind of PostgreSQL types.

Constructors

PGbool

logical Boolean (true/false)

PGint2

signed two-byte integer

PGint4

signed four-byte integer

PGint8

signed eight-byte integer

PGnumeric

arbitrary precision numeric type

PGfloat4

single precision floating-point number (4 bytes)

PGfloat8

double precision floating-point number (8 bytes)

PGchar Nat

fixed-length character string

PGvarchar Nat

variable-length character string

PGtext

variable-length character string

PGbytea

binary data ("byte array")

PGtimestamp

date and time (no time zone)

PGtimestamptz

date and time, including time zone

PGdate

calendar date (year, month, day)

PGtime

time of day (no time zone)

PGtimetz

time of day, including time zone

PGinterval

time span

PGuuid

universally unique identifier

PGinet

IPv4 or IPv6 host address

PGjson

textual JSON data

PGjsonb

binary JSON data, decomposed

UnsafePGType Symbol

an escape hatch for unsupported PostgreSQL types

Instances

PGAvg PGType PGint2 PGnumeric Source # 

Methods

avg :: Expression tables Ungrouped params (Required (nullity PGnumeric)) -> Expression tables (Grouped bys) params (Required (nullity avg)) Source #

avgDistinct :: Expression tables Ungrouped params (Required (nullity PGnumeric)) -> Expression tables (Grouped bys) params (Required (nullity avg)) Source #

PGAvg PGType PGint4 PGnumeric Source # 

Methods

avg :: Expression tables Ungrouped params (Required (nullity PGnumeric)) -> Expression tables (Grouped bys) params (Required (nullity avg)) Source #

avgDistinct :: Expression tables Ungrouped params (Required (nullity PGnumeric)) -> Expression tables (Grouped bys) params (Required (nullity avg)) Source #

PGAvg PGType PGint8 PGnumeric Source # 

Methods

avg :: Expression tables Ungrouped params (Required (nullity PGnumeric)) -> Expression tables (Grouped bys) params (Required (nullity avg)) Source #

avgDistinct :: Expression tables Ungrouped params (Required (nullity PGnumeric)) -> Expression tables (Grouped bys) params (Required (nullity avg)) Source #

PGAvg PGType PGnumeric PGnumeric Source # 

Methods

avg :: Expression tables Ungrouped params (Required (nullity PGnumeric)) -> Expression tables (Grouped bys) params (Required (nullity avg)) Source #

avgDistinct :: Expression tables Ungrouped params (Required (nullity PGnumeric)) -> Expression tables (Grouped bys) params (Required (nullity avg)) Source #

PGAvg PGType PGfloat4 PGfloat8 Source # 

Methods

avg :: Expression tables Ungrouped params (Required (nullity PGfloat8)) -> Expression tables (Grouped bys) params (Required (nullity avg)) Source #

avgDistinct :: Expression tables Ungrouped params (Required (nullity PGfloat8)) -> Expression tables (Grouped bys) params (Required (nullity avg)) Source #

PGAvg PGType PGfloat8 PGfloat8 Source # 

Methods

avg :: Expression tables Ungrouped params (Required (nullity PGfloat8)) -> Expression tables (Grouped bys) params (Required (nullity avg)) Source #

avgDistinct :: Expression tables Ungrouped params (Required (nullity PGfloat8)) -> Expression tables (Grouped bys) params (Required (nullity avg)) Source #

PGAvg PGType PGinterval PGinterval Source # 

Methods

avg :: Expression tables Ungrouped params (Required (nullity PGinterval)) -> Expression tables (Grouped bys) params (Required (nullity avg)) Source #

avgDistinct :: Expression tables Ungrouped params (Required (nullity PGinterval)) -> Expression tables (Grouped bys) params (Required (nullity avg)) Source #

data NullityType Source #

NullityType encodes the potential presence or definite absence of a NULL allowing operations which are sensitive to such to be well typed.

Constructors

Null PGType

NULL may be present

NotNull PGType

NULL is absent

data ColumnType Source #

ColumnType encodes the allowance of DEFAULT and the only way to generate an Optional Expression is to use def, unDef or param.

Constructors

Optional NullityType

DEFAULT is allowed

Required NullityType

DEFAULT is not allowed

Instances

Category TablesType Definition # 

Methods

id :: cat a a #

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

(KnownSymbol table, HasTable table schema columns) => HasTable table ((:) (Symbol, ColumnsType) table' schema) columns Source # 

Methods

getTable :: Alias table -> Table (((Symbol, ColumnsType) ': table') schema) columns Source #

KnownSymbol table => HasTable table ((:) (Symbol, ColumnsType) ((:::) ColumnsType table columns) tables) columns Source # 

Methods

getTable :: Alias table -> Table (((Symbol, ColumnsType) ': (ColumnsType ::: table) columns) tables) columns Source #

(KnownSymbol column, HasColumn column table ty) => HasColumn column ((:) (Symbol, ColumnType) ty' table) ty Source # 

Methods

getColumn :: HasUnique ColumnsType table tables (((Symbol, ColumnType) ': ty') table) => Alias column -> Expression tables Ungrouped params ty Source #

(KnownNat n, HasParameter ((-) n 1) params ty) => HasParameter n ((:) ColumnType ty' params) ty Source # 

Methods

param :: Expression tables grouping ((ColumnType ': ty') params) ty Source #

PGTyped (BaseType ty1) => HasParameter 1 ((:) ColumnType ty1 tys) ty1 Source # 

Methods

param :: Expression tables grouping ((ColumnType ': ty1) tys) ty1 Source #

KnownSymbol column => HasColumn column ((:) (Symbol, ColumnType) ((:::) ColumnType column (optionality ty)) tys) (Required ty) Source # 

Methods

getColumn :: HasUnique ColumnsType table tables (((Symbol, ColumnType) ': (ColumnType ::: column) (optionality ty)) tys) => Alias column -> Expression tables Ungrouped params (Required ty) Source #

(~) FieldName field column => SameField (FieldInfo field) ((:::) ColumnType column ty) Source # 
FromValue pg y => FromColumnValue ((:::) ColumnType column (Required (NotNull pg))) y Source # 
FromValue pg y => FromColumnValue ((:::) ColumnType column (Required (Null pg))) (Maybe y) Source # 

type ColumnsType = [(Symbol, ColumnType)] Source #

ColumnsType is a kind synonym for a row of ColumnTypes.

type TablesType = [(Symbol, ColumnsType)] Source #

TablesType is a kind synonym for a row of ColumnsTypes. It is used as a kind for both a schema, a disjoint union of tables, and a joined table FromClause, a product of tables.

data Grouping Source #

Grouping is an auxiliary namespace, created by GROUP BY clauses (group), and used for typesafe aggregation

Constructors

Ungrouped 
Grouped [(Symbol, Symbol)] 

Constraints

type PGNum ty = In ty '[PGint2, PGint4, PGint8, PGnumeric, PGfloat4, PGfloat8] Source #

PGNum is a constraint on PGType whose Expressions have a Num constraint.

type PGIntegral ty = In ty '[PGint2, PGint4, PGint8] Source #

PGIntegral is a constraint on PGType whose Expressions have div_ and mod_ functions.

type PGFloating ty = In ty '[PGfloat4, PGfloat8, PGnumeric] Source #

PGFloating is a constraint on PGType whose Expressions have Fractional and Floating constraints.

Aliases

type (:::) (alias :: Symbol) (ty :: polykind) = '(alias, ty) Source #

::: is like a promoted version of As, a type level pair between an alias and some type, usually a column alias and a ColumnType or a table alias and a ColumnsType.

data Alias (alias :: Symbol) Source #

Aliases are proxies for a type level string or Symbol and have an IsLabel instance so that with -XOverloadedLabels

>>> :set -XOverloadedLabels
>>> #foobar :: Alias "foobar"
Alias

Constructors

Alias 

Instances

IsTableColumn table column (Alias table, Alias column) Source # 

Methods

(!) :: Alias table -> Alias column -> (Alias table, Alias column) Source #

(~) Symbol alias1 alias2 => IsLabel alias1 (Alias alias2) Source # 

Methods

fromLabel :: Alias alias2 #

Eq (Alias alias) Source # 

Methods

(==) :: Alias alias -> Alias alias -> Bool #

(/=) :: Alias alias -> Alias alias -> Bool #

Ord (Alias alias) Source # 

Methods

compare :: Alias alias -> Alias alias -> Ordering #

(<) :: Alias alias -> Alias alias -> Bool #

(<=) :: Alias alias -> Alias alias -> Bool #

(>) :: Alias alias -> Alias alias -> Bool #

(>=) :: Alias alias -> Alias alias -> Bool #

max :: Alias alias -> Alias alias -> Alias alias #

min :: Alias alias -> Alias alias -> Alias alias #

Show (Alias alias) Source # 

Methods

showsPrec :: Int -> Alias alias -> ShowS #

show :: Alias alias -> String #

showList :: [Alias alias] -> ShowS #

Generic (Alias alias) Source # 

Associated Types

type Rep (Alias alias) :: * -> * #

Methods

from :: Alias alias -> Rep (Alias alias) x #

to :: Rep (Alias alias) x -> Alias alias #

NFData (Alias alias) Source # 

Methods

rnf :: Alias alias -> () #

type Rep (Alias alias) Source # 
type Rep (Alias alias) = D1 * (MetaData "Alias" "Squeal.PostgreSQL.Schema" "squeal-postgresql-0.1.0.0-InKixIU9ozz9ruvOz17xcO" False) (C1 * (MetaCons "Alias" PrefixI False) (U1 *))

renderAlias :: KnownSymbol alias => Alias alias -> ByteString Source #

>>> renderAlias #alias
"alias"

data Aliased expression aliased where Source #

The As operator is used to name an expression. As is like a demoted version of :::.

>>> Just "hello" `As` #hi :: Aliased Maybe ("hi" ::: String)
As (Just "hello") Alias

Constructors

As :: KnownSymbol alias => expression ty -> Alias alias -> Aliased expression (alias ::: ty) 

Instances

Eq (expression ty) => Eq (Aliased polykind expression ((:::) polykind alias ty)) Source # 

Methods

(==) :: Aliased polykind expression ((polykind ::: alias) ty) -> Aliased polykind expression ((polykind ::: alias) ty) -> Bool #

(/=) :: Aliased polykind expression ((polykind ::: alias) ty) -> Aliased polykind expression ((polykind ::: alias) ty) -> Bool #

Ord (expression ty) => Ord (Aliased polykind expression ((:::) polykind alias ty)) Source # 

Methods

compare :: Aliased polykind expression ((polykind ::: alias) ty) -> Aliased polykind expression ((polykind ::: alias) ty) -> Ordering #

(<) :: Aliased polykind expression ((polykind ::: alias) ty) -> Aliased polykind expression ((polykind ::: alias) ty) -> Bool #

(<=) :: Aliased polykind expression ((polykind ::: alias) ty) -> Aliased polykind expression ((polykind ::: alias) ty) -> Bool #

(>) :: Aliased polykind expression ((polykind ::: alias) ty) -> Aliased polykind expression ((polykind ::: alias) ty) -> Bool #

(>=) :: Aliased polykind expression ((polykind ::: alias) ty) -> Aliased polykind expression ((polykind ::: alias) ty) -> Bool #

max :: Aliased polykind expression ((polykind ::: alias) ty) -> Aliased polykind expression ((polykind ::: alias) ty) -> Aliased polykind expression ((polykind ::: alias) ty) #

min :: Aliased polykind expression ((polykind ::: alias) ty) -> Aliased polykind expression ((polykind ::: alias) ty) -> Aliased polykind expression ((polykind ::: alias) ty) #

Show (expression ty) => Show (Aliased polykind expression ((:::) polykind alias ty)) Source # 

Methods

showsPrec :: Int -> Aliased polykind expression ((polykind ::: alias) ty) -> ShowS #

show :: Aliased polykind expression ((polykind ::: alias) ty) -> String #

showList :: [Aliased polykind expression ((polykind ::: alias) ty)] -> ShowS #

renderAliased :: (forall ty. expression ty -> ByteString) -> Aliased expression aliased -> ByteString Source #

>>> let renderMaybe = fromString . maybe "Nothing" (const "Just")
>>> renderAliased renderMaybe (Just (3::Int) `As` #an_int)
"Just AS an_int"

class IsLabel (x :: Symbol) a where #

Minimal complete definition

fromLabel

Methods

fromLabel :: a #

Instances

(~) Symbol alias1 alias2 => IsLabel alias1 (Alias alias2) # 

Methods

fromLabel :: Alias alias2 #

HasTable table schema columns => IsLabel table (Table schema columns) # 

Methods

fromLabel :: Table schema columns #

(HasUnique ColumnsType table tables columns, HasColumn column columns ty, GroupedBy table column bys) => IsLabel column (Expression tables (Grouped bys) params ty) # 

Methods

fromLabel :: Expression tables (Grouped bys) params ty #

(HasColumn column columns ty, HasUnique ColumnsType table tables columns) => IsLabel column (Expression tables Ungrouped params ty) # 

Methods

fromLabel :: Expression tables Ungrouped params ty #

class IsTableColumn table column expression where Source #

Analagous to IsLabel, the constraint IsTableColumn defines ! for a column alias qualified by a table alias.

Minimal complete definition

(!)

Methods

(!) :: Alias table -> Alias column -> expression infixl 9 Source #

Instances

IsTableColumn table column (Alias table, Alias column) Source # 

Methods

(!) :: Alias table -> Alias column -> (Alias table, Alias column) Source #

(HasTable table tables columns, HasColumn column columns ty, GroupedBy table column bys) => IsTableColumn table column (Expression tables (Grouped bys) params ty) Source # 

Methods

(!) :: Alias table -> Alias column -> Expression tables (Grouped bys) params ty Source #

(HasTable table tables columns, HasColumn column columns ty) => IsTableColumn table column (Expression tables Ungrouped params ty) Source # 

Methods

(!) :: Alias table -> Alias column -> Expression tables Ungrouped params ty Source #

Type Families

type family In x xs :: Constraint where ... Source #

In x xs is a constraint that proves that x is in xs.

Equations

In x (x ': xs) = () 
In x (y ': xs) = In x xs 

type HasUnique alias xs x = xs ~ '[alias ::: x] Source #

HasUnique alias xs x is a constraint that proves that xs is a singleton of alias ::: x.

type family BaseType (ty :: ColumnType) :: PGType where ... Source #

BaseType forgets about NULL and DEFAULT

Equations

BaseType (optionality (nullity pg)) = pg 

type family SameTypes (columns0 :: ColumnsType) (columns1 :: ColumnsType) :: Constraint where ... Source #

SameTypes is a constraint that proves two ColumnsTypes have the same length and the same ColumnTypes.

Equations

SameTypes '[] '[] = () 
SameTypes ((column0 ::: ty0) ': columns0) ((column1 ::: ty1) ': columns1) = (ty0 ~ ty1, SameTypes columns0 columns1) 

type family AllNotNull (columns :: ColumnsType) :: Constraint where ... Source #

AllNotNull is a constraint that proves a ColumnsType has no NULLs.

Equations

AllNotNull '[] = () 
AllNotNull ((column ::: optionality (NotNull ty)) ': columns) = AllNotNull columns 

type family NotAllNull columns :: Constraint where ... Source #

NotAllNull is a constraint that proves a ColumnsType has some NOT NULL.

Equations

NotAllNull ((column ::: optionality (NotNull ty)) ': columns) = () 
NotAllNull ((column ::: optionality (Null ty)) ': columns) = NotAllNull columns 

type family NullifyType (ty :: ColumnType) :: ColumnType where ... Source #

NullifyType is an idempotent that nullifies a ColumnType.

Equations

NullifyType (optionality (Null ty)) = optionality (Null ty) 
NullifyType (optionality (NotNull ty)) = optionality (Null ty) 

type family NullifyColumns (columns :: ColumnsType) :: ColumnsType where ... Source #

NullifyColumns is an idempotent that nullifies a ColumnsType.

Equations

NullifyColumns '[] = '[] 
NullifyColumns ((column ::: ty) ': columns) = (column ::: NullifyType ty) ': NullifyColumns columns 

type family NullifyTables (tables :: TablesType) :: TablesType where ... Source #

NullifyTables is an idempotent that nullifies a TablesType used to nullify the left or right hand side of an outer join in a FromClause.

Equations

NullifyTables '[] = '[] 
NullifyTables ((table ::: columns) ': tables) = (table ::: NullifyColumns columns) ': NullifyTables tables 

type family Join xs ys where ... Source #

Join is simply promoted ++ and is used in JOINs in FromClauses.

Equations

Join '[] ys = ys 
Join (x ': xs) ys = x ': Join xs ys 

type family Create alias x xs where ... Source #

Create alias x xs adds alias ::: x to the end of xs and is used in createTable statements and in ALTER TABLE addColumnDefault and addColumnNull statements.

Equations

Create alias x '[] = '[alias ::: x] 
Create alias y (x ': xs) = x ': Create alias y xs 

type family Drop alias xs where ... Source #

Drop alias xs removes the type associated with alias in xs and is used in dropTable statements and in ALTER TABLE dropColumn statements.

Equations

Drop alias ((alias ::: x) ': xs) = xs 
Drop alias (x ': xs) = x ': Drop alias xs 

type family Alter alias xs x where ... Source #

Alter alias xs x replaces the type associated with an alias in xs with the type x and is used in alterTable and alterColumn.

Equations

Alter alias ((alias ::: x0) ': xs) x1 = (alias ::: x1) ': xs 
Alter alias (x0 ': xs) x1 = x0 ': Alter alias xs x1 

type family Rename alias0 alias1 xs where ... Source #

Rename alias0 alias1 xs replaces the alias alias0 by alias1 in xs and is used in alterTableRename and renameColumn.

Equations

Rename alias0 alias1 ((alias0 ::: x0) ': xs) = (alias1 ::: x0) ': xs 
Rename alias0 alias1 (x ': xs) = x ': Rename alias0 alias1 xs 

Generics

class SameField (fieldInfo :: FieldInfo) (fieldty :: (Symbol, ColumnType)) Source #

A SameField constraint is an equality constraint on a FieldInfo and the column alias in a ::: pair.

Instances

(~) FieldName field column => SameField (FieldInfo field) ((:::) ColumnType column ty) Source # 

type family SameFields (datatypeInfo :: DatatypeInfo) (columns :: ColumnsType) :: Constraint where ... Source #

A SameFields constraint proves that a DatatypeInfo of a record type has the same field names as the column aliases of a ColumnsType.

Equations

SameFields (ADT _module _datatype '[Record _constructor fields]) columns = AllZip SameField fields columns 
SameFields (Newtype _module _datatype (Record _constructor fields)) columns = AllZip SameField fields columns