squeal-postgresql-0.4.0.0: Squeal PostgreSQL Library

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

Squeal.PostgreSQL.Schema

Contents

Description

This module provides a type-level DSL for kinds of Postgres types, tables, schema, constraints, aliases, enumerated labels, and groupings. It also defines useful type families to operate on these. Finally, it defines an embedding of Haskell types into Postgres types.

Synopsis

Postgres Types

data PGType Source #

PGType is the promoted datakind of PostgreSQL types.

>>> import Squeal.PostgreSQL.Schema
>>> :kind 'PGbool
'PGbool :: PGType

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

PGvararray NullityType

variable length array

PGfixarray Nat NullityType

fixed length array

PGenum [Symbol]

enumerated (enum) types are data types that comprise a static, ordered set of values.

PGcomposite RowType

a composite type represents the structure of a row or record; it is essentially just a list of field names and their data types.

UnsafePGType Symbol

an escape hatch for unsupported PostgreSQL types

Instances
PGAvg PGint2 PGnumeric Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

avg :: Expression schema from Ungrouped params (nullity PGint2) -> Expression schema from (Grouped bys) params (nullity PGnumeric) Source #

avgDistinct :: Expression schema from Ungrouped params (nullity PGint2) -> Expression schema from (Grouped bys) params (nullity PGnumeric) Source #

PGAvg PGint4 PGnumeric Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

avg :: Expression schema from Ungrouped params (nullity PGint4) -> Expression schema from (Grouped bys) params (nullity PGnumeric) Source #

avgDistinct :: Expression schema from Ungrouped params (nullity PGint4) -> Expression schema from (Grouped bys) params (nullity PGnumeric) Source #

PGAvg PGint8 PGnumeric Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

avg :: Expression schema from Ungrouped params (nullity PGint8) -> Expression schema from (Grouped bys) params (nullity PGnumeric) Source #

avgDistinct :: Expression schema from Ungrouped params (nullity PGint8) -> Expression schema from (Grouped bys) params (nullity PGnumeric) Source #

PGAvg PGnumeric PGnumeric Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

avg :: Expression schema from Ungrouped params (nullity PGnumeric) -> Expression schema from (Grouped bys) params (nullity PGnumeric) Source #

avgDistinct :: Expression schema from Ungrouped params (nullity PGnumeric) -> Expression schema from (Grouped bys) params (nullity PGnumeric) Source #

PGAvg PGfloat4 PGfloat8 Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

avg :: Expression schema from Ungrouped params (nullity PGfloat4) -> Expression schema from (Grouped bys) params (nullity PGfloat8) Source #

avgDistinct :: Expression schema from Ungrouped params (nullity PGfloat4) -> Expression schema from (Grouped bys) params (nullity PGfloat8) Source #

PGAvg PGfloat8 PGfloat8 Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

avg :: Expression schema from Ungrouped params (nullity PGfloat8) -> Expression schema from (Grouped bys) params (nullity PGfloat8) Source #

avgDistinct :: Expression schema from Ungrouped params (nullity PGfloat8) -> Expression schema from (Grouped bys) params (nullity PGfloat8) Source #

PGAvg PGinterval PGinterval Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

avg :: Expression schema from Ungrouped params (nullity PGinterval) -> Expression schema from (Grouped bys) params (nullity PGinterval) Source #

avgDistinct :: Expression schema from Ungrouped params (nullity PGinterval) -> Expression schema from (Grouped bys) params (nullity PGinterval) 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.

>>> :kind 'Null 'PGint4
'Null 'PGint4 :: NullityType
>>> :kind 'NotNull ('PGvarchar 50)
'NotNull ('PGvarchar 50) :: NullityType

Constructors

Null PGType

NULL may be present

NotNull PGType

NULL is absent

Instances
(Has table from columns, Has column columns ty, GroupedBy table column bys) => IsQualified table column (NP (Aliased (Expression schema from (Grouped bys) params)) ((column ::: ty) ': ([] :: [(Symbol, NullityType)]))) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(!) :: Alias table -> Alias column -> NP (Aliased (Expression schema from (Grouped bys) params)) ((column ::: ty) ': []) Source #

(Has table from columns, Has column columns ty, GroupedBy table column bys) => IsQualified table column (Aliased (Expression schema from (Grouped bys) params) (column ::: ty)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

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

(Has table from columns, Has column columns ty) => IsQualified table column (NP (Aliased (Expression schema from Ungrouped params)) ((column ::: ty) ': ([] :: [(Symbol, NullityType)]))) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(!) :: Alias table -> Alias column -> NP (Aliased (Expression schema from Ungrouped params)) ((column ::: ty) ': []) Source #

(Has table from columns, Has column columns ty) => IsQualified table column (Aliased (Expression schema from Ungrouped params) (column ::: ty)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(!) :: Alias table -> Alias column -> Aliased (Expression schema from Ungrouped params) (column ::: ty) Source #

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

Defined in Squeal.PostgreSQL.Expression

Methods

parameter :: TypeExpression schema ty -> Expression schema from grouping (ty' ': params) ty Source #

HasParameter 1 schema (ty1 ': tys) ty1 Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

parameter :: TypeExpression schema ty1 -> Expression schema from grouping (ty1 ': tys) ty1 Source #

(HasUnique table from columns, Has column columns ty, GroupedBy table column bys) => IsLabel column (NP (Aliased (Expression schema from (Grouped bys) params)) ((column ::: ty) ': ([] :: [(Symbol, NullityType)]))) # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: NP (Aliased (Expression schema from (Grouped bys) params)) ((column ::: ty) ': []) #

(HasUnique table from columns, Has column columns ty, GroupedBy table column bys) => IsLabel column (Aliased (Expression schema from (Grouped bys) params) (column ::: ty)) # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: Aliased (Expression schema from (Grouped bys) params) (column ::: ty) #

(HasUnique table from columns, Has column columns ty) => IsLabel column (NP (Aliased (Expression schema from Ungrouped params)) ((column ::: ty) ': ([] :: [(Symbol, NullityType)]))) # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: NP (Aliased (Expression schema from Ungrouped params)) ((column ::: ty) ': []) #

(HasUnique table from columns, Has column columns ty) => IsLabel column (Aliased (Expression schema from Ungrouped params) (column ::: ty)) # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: Aliased (Expression schema from Ungrouped params) (column ::: ty) #

ty0 ~ ty1 => SamePGType (alias0 ::: (def0 :=> nullity0 ty0)) (alias1 ::: (def1 :=> nullity1 ty1)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

AddColumn (Def :=> ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition

Methods

addColumn :: (KnownSymbol column, Has tab schema (Table table0), table0 ~ (constraints :=> columns), table1 ~ (constraints :=> Create column (Def :=> ty) columns)) => Alias column -> ColumnTypeExpression schema (Def :=> ty) -> AlterTable tab table1 schema Source #

AddColumn (NoDef :=> Null ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition

Methods

addColumn :: (KnownSymbol column, Has tab schema (Table table0), table0 ~ (constraints :=> columns), table1 ~ (constraints :=> Create column (NoDef :=> Null ty) columns)) => Alias column -> ColumnTypeExpression schema (NoDef :=> Null ty) -> AlterTable tab table1 schema Source #

type RowType = [(Symbol, NullityType)] Source #

A RowType is a row of NullityType. They correspond to Haskell record types by means of RowPG and are used in many places.

>>> :{
type family PersonRow :: RowType where
  PersonRow =
    '[ "name"        ::: 'NotNull 'PGtext
     , "age"         ::: 'NotNull 'PGint4
     , "dateOfBirth" :::    'Null 'PGdate
     ]
:}

type FromType = [(Symbol, RowType)] Source #

FromType is a row of RowTypes. It can be thought of as a product, or horizontal gluing and is used in FromClauses and TableExpressions.

Haskell to Postgres Types

type family PG (hask :: Type) :: PGType Source #

The PG type family embeds a subset of Haskell types as Postgres types. As an open type family, PG is extensible.

>>> :kind! PG LocalTime
PG LocalTime :: PGType
= 'PGtimestamp
>>> newtype MyDouble = My Double
>>> type instance PG MyDouble = 'PGfloat8
Instances
type PG Bool Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG Bool = PGbool
type PG Char Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG Char = PGchar 1
type PG Double Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG Float Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG Int16 Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG Int16 = PGint2
type PG Int32 Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG Int32 = PGint4
type PG Int64 Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG Int64 = PGint8
type PG Word16 Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG Word32 Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG Word64 Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG ByteString Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG ByteString Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG Scientific Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG String Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG Text Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG Text = PGtext
type PG UTCTime Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG Value Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG Value = PGjson
type PG Text Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG Text = PGtext
type PG UUID Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG UUID = PGuuid
type PG Day Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG Day = PGdate
type PG DiffTime Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG TimeOfDay Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG LocalTime Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG (NetAddr IP) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG (NetAddr IP) = PGinet
type PG (Vector hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG (Vector hask) = PGvararray (NullPG hask)
type PG (Enumerated hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG (Enumerated hask) = PGenum (LabelsPG hask)
type PG (Composite hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG (Composite hask) = PGcomposite (RowPG hask)
type PG (Jsonb hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG (Jsonb hask) = PGjsonb
type PG (Json hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG (Json hask) = PGjson
type PG (hask, hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG (hask, hask) = PGfixarray 2 (NullPG hask)
type PG (TimeOfDay, TimeZone) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG (hask, hask, hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG (hask, hask, hask) = PGfixarray 3 (NullPG hask)
type PG (hask, hask, hask, hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG (hask, hask, hask, hask) = PGfixarray 4 (NullPG hask)
type PG (hask, hask, hask, hask, hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG (hask, hask, hask, hask, hask) = PGfixarray 5 (NullPG hask)
type PG (hask, hask, hask, hask, hask, hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG (hask, hask, hask, hask, hask, hask) = PGfixarray 6 (NullPG hask)
type PG (hask, hask, hask, hask, hask, hask, hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG (hask, hask, hask, hask, hask, hask, hask) = PGfixarray 7 (NullPG hask)
type PG (hask, hask, hask, hask, hask, hask, hask, hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG (hask, hask, hask, hask, hask, hask, hask, hask) = PGfixarray 8 (NullPG hask)
type PG (hask, hask, hask, hask, hask, hask, hask, hask, hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG (hask, hask, hask, hask, hask, hask, hask, hask, hask) = PGfixarray 9 (NullPG hask)
type PG (hask, hask, hask, hask, hask, hask, hask, hask, hask, hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG (hask, hask, hask, hask, hask, hask, hask, hask, hask, hask) = PGfixarray 10 (NullPG hask)

type family NullPG (hask :: Type) :: NullityType where ... Source #

NullPG turns a Haskell type into a NullityType.

>>> :kind! NullPG Double
NullPG Double :: NullityType
= 'NotNull 'PGfloat8
>>> :kind! NullPG (Maybe Double)
NullPG (Maybe Double) :: NullityType
= 'Null 'PGfloat8

Equations

NullPG (Maybe hask) = Null (PG hask) 
NullPG hask = NotNull (PG hask) 

type family TuplePG (hask :: Type) :: [NullityType] where ... Source #

TuplePG turns a Haskell tuple type (including record types) into the corresponding list of NullityTypes.

>>> :kind! TuplePG (Double, Maybe Char)
TuplePG (Double, Maybe Char) :: [NullityType]
= '['NotNull 'PGfloat8, 'Null ('PGchar 1)]

Equations

TuplePG hask = TupleOf (TupleCodeOf hask (Code hask)) 

type family RowPG (hask :: Type) :: RowType where ... Source #

RowPG turns a Haskell record type into a RowType.

>>> data Person = Person { name :: Text, age :: Int32 } deriving GHC.Generic
>>> instance Generic Person
>>> instance HasDatatypeInfo Person
>>> :kind! RowPG Person
RowPG Person :: [(Symbol, NullityType)]
= '["name" ::: 'NotNull 'PGtext, "age" ::: 'NotNull 'PGint4]

Equations

RowPG hask = RowOf (RecordCodeOf hask) 

newtype Json hask Source #

The Json newtype is an indication that the Haskell type it's applied to should be stored as PGjson.

Constructors

Json 

Fields

Instances
FromJSON x => FromValue PGjson (Json x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

fromValue :: Value (Json x) Source #

Eq hask => Eq (Json hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

(==) :: Json hask -> Json hask -> Bool #

(/=) :: Json hask -> Json hask -> Bool #

Ord hask => Ord (Json hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

compare :: Json hask -> Json hask -> Ordering #

(<) :: Json hask -> Json hask -> Bool #

(<=) :: Json hask -> Json hask -> Bool #

(>) :: Json hask -> Json hask -> Bool #

(>=) :: Json hask -> Json hask -> Bool #

max :: Json hask -> Json hask -> Json hask #

min :: Json hask -> Json hask -> Json hask #

Read hask => Read (Json hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

readsPrec :: Int -> ReadS (Json hask) #

readList :: ReadS [Json hask] #

readPrec :: ReadPrec (Json hask) #

readListPrec :: ReadPrec [Json hask] #

Show hask => Show (Json hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

showsPrec :: Int -> Json hask -> ShowS #

show :: Json hask -> String #

showList :: [Json hask] -> ShowS #

Generic (Json hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Associated Types

type Rep (Json hask) :: * -> * #

Methods

from :: Json hask -> Rep (Json hask) x #

to :: Rep (Json hask) x -> Json hask #

ToJSON x => ToParam (Json x) PGjson Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

type Rep (Json hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type Rep (Json hask) = D1 (MetaData "Json" "Squeal.PostgreSQL.Schema" "squeal-postgresql-0.4.0.0-GuxxUOwtUmZB6qL3MLEXvb" True) (C1 (MetaCons "Json" PrefixI True) (S1 (MetaSel (Just "getJson") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 hask)))
type PG (Json hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG (Json hask) = PGjson

newtype Jsonb hask Source #

The Jsonb newtype is an indication that the Haskell type it's applied to should be stored as PGjsonb.

Constructors

Jsonb 

Fields

Instances
FromJSON x => FromValue PGjsonb (Jsonb x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

fromValue :: Value (Jsonb x) Source #

Eq hask => Eq (Jsonb hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

(==) :: Jsonb hask -> Jsonb hask -> Bool #

(/=) :: Jsonb hask -> Jsonb hask -> Bool #

Ord hask => Ord (Jsonb hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

compare :: Jsonb hask -> Jsonb hask -> Ordering #

(<) :: Jsonb hask -> Jsonb hask -> Bool #

(<=) :: Jsonb hask -> Jsonb hask -> Bool #

(>) :: Jsonb hask -> Jsonb hask -> Bool #

(>=) :: Jsonb hask -> Jsonb hask -> Bool #

max :: Jsonb hask -> Jsonb hask -> Jsonb hask #

min :: Jsonb hask -> Jsonb hask -> Jsonb hask #

Read hask => Read (Jsonb hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

readsPrec :: Int -> ReadS (Jsonb hask) #

readList :: ReadS [Jsonb hask] #

readPrec :: ReadPrec (Jsonb hask) #

readListPrec :: ReadPrec [Jsonb hask] #

Show hask => Show (Jsonb hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

showsPrec :: Int -> Jsonb hask -> ShowS #

show :: Jsonb hask -> String #

showList :: [Jsonb hask] -> ShowS #

Generic (Jsonb hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Associated Types

type Rep (Jsonb hask) :: * -> * #

Methods

from :: Jsonb hask -> Rep (Jsonb hask) x #

to :: Rep (Jsonb hask) x -> Jsonb hask #

ToJSON x => ToParam (Jsonb x) PGjsonb Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

type Rep (Jsonb hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type Rep (Jsonb hask) = D1 (MetaData "Jsonb" "Squeal.PostgreSQL.Schema" "squeal-postgresql-0.4.0.0-GuxxUOwtUmZB6qL3MLEXvb" True) (C1 (MetaCons "Jsonb" PrefixI True) (S1 (MetaSel (Just "getJsonb") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 hask)))
type PG (Jsonb hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG (Jsonb hask) = PGjsonb

newtype Composite record Source #

The Composite newtype is an indication that the Haskell type it's applied to should be stored as a PGcomposite.

Constructors

Composite 

Fields

Instances
Eq record => Eq (Composite record) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

(==) :: Composite record -> Composite record -> Bool #

(/=) :: Composite record -> Composite record -> Bool #

Ord record => Ord (Composite record) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

compare :: Composite record -> Composite record -> Ordering #

(<) :: Composite record -> Composite record -> Bool #

(<=) :: Composite record -> Composite record -> Bool #

(>) :: Composite record -> Composite record -> Bool #

(>=) :: Composite record -> Composite record -> Bool #

max :: Composite record -> Composite record -> Composite record #

min :: Composite record -> Composite record -> Composite record #

Read record => Read (Composite record) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

readsPrec :: Int -> ReadS (Composite record) #

readList :: ReadS [Composite record] #

readPrec :: ReadPrec (Composite record) #

readListPrec :: ReadPrec [Composite record] #

Show record => Show (Composite record) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

showsPrec :: Int -> Composite record -> ShowS #

show :: Composite record -> String #

showList :: [Composite record] -> ShowS #

Generic (Composite record) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Associated Types

type Rep (Composite record) :: * -> * #

Methods

from :: Composite record -> Rep (Composite record) x #

to :: Rep (Composite record) x -> Composite record #

FromRow fields y => FromValue (PGcomposite fields) (Composite y) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

(SListI fields, IsRecord x xs, AllZip ToField xs fields, All HasAliasedOid fields) => ToParam (Composite x) (PGcomposite fields) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

toParam :: Composite x -> K Encoding (PGcomposite fields) Source #

type Rep (Composite record) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type Rep (Composite record) = D1 (MetaData "Composite" "Squeal.PostgreSQL.Schema" "squeal-postgresql-0.4.0.0-GuxxUOwtUmZB6qL3MLEXvb" True) (C1 (MetaCons "Composite" PrefixI True) (S1 (MetaSel (Just "getComposite") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 record)))
type PG (Composite hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG (Composite hask) = PGcomposite (RowPG hask)

newtype Enumerated enum Source #

The Enumerated newtype is an indication that the Haskell type it's applied to should be stored as PGenum.

Constructors

Enumerated 

Fields

Instances
Eq enum => Eq (Enumerated enum) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

(==) :: Enumerated enum -> Enumerated enum -> Bool #

(/=) :: Enumerated enum -> Enumerated enum -> Bool #

Ord enum => Ord (Enumerated enum) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

compare :: Enumerated enum -> Enumerated enum -> Ordering #

(<) :: Enumerated enum -> Enumerated enum -> Bool #

(<=) :: Enumerated enum -> Enumerated enum -> Bool #

(>) :: Enumerated enum -> Enumerated enum -> Bool #

(>=) :: Enumerated enum -> Enumerated enum -> Bool #

max :: Enumerated enum -> Enumerated enum -> Enumerated enum #

min :: Enumerated enum -> Enumerated enum -> Enumerated enum #

Read enum => Read (Enumerated enum) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Show enum => Show (Enumerated enum) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

showsPrec :: Int -> Enumerated enum -> ShowS #

show :: Enumerated enum -> String #

showList :: [Enumerated enum] -> ShowS #

Generic (Enumerated enum) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Associated Types

type Rep (Enumerated enum) :: * -> * #

Methods

from :: Enumerated enum -> Rep (Enumerated enum) x #

to :: Rep (Enumerated enum) x -> Enumerated enum #

(IsEnumType y, HasDatatypeInfo y, LabelsPG y ~ labels) => FromValue (PGenum labels) (Enumerated y) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

(IsEnumType x, HasDatatypeInfo x, LabelsPG x ~ labels) => ToParam (Enumerated x) (PGenum labels) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

toParam :: Enumerated x -> K Encoding (PGenum labels) Source #

type Rep (Enumerated enum) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type Rep (Enumerated enum) = D1 (MetaData "Enumerated" "Squeal.PostgreSQL.Schema" "squeal-postgresql-0.4.0.0-GuxxUOwtUmZB6qL3MLEXvb" True) (C1 (MetaCons "Enumerated" PrefixI True) (S1 (MetaSel (Just "getEnumerated") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 enum)))
type PG (Enumerated hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type PG (Enumerated hask) = PGenum (LabelsPG hask)

Schema Types

type ColumnType = (ColumnConstraint, NullityType) Source #

ColumnType encodes the allowance of DEFAULT and NULL and the base PGType for a column.

>>> :set -XTypeFamilies -XTypeInType
>>> import GHC.TypeLits
>>> type family IdColumn :: ColumnType where IdColumn = 'Def :=> 'NotNull 'PGint4
>>> type family EmailColumn :: ColumnType where EmailColumn = 'NoDef :=> 'Null 'PGtext

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

ColumnsType is a row of ColumnTypes.

>>> :{
type family UsersColumns :: ColumnsType where
  UsersColumns =
    '[ "name" ::: 'NoDef :=> 'NotNull 'PGtext
     , "id"   :::   'Def :=> 'NotNull 'PGint4
     ]
:}

type TableType = (TableConstraints, ColumnsType) Source #

TableType encodes a row of constraints on a table as well as the types of its columns.

>>> :{
type family UsersTable :: TableType where
  UsersTable =
    '[ "pk_users" ::: 'PrimaryKey '["id"] ] :=>
    '[ "id"       :::   'Def :=> 'NotNull 'PGint4
     , "name"     ::: 'NoDef :=> 'NotNull 'PGtext
     ]
:}

data SchemumType Source #

A SchemumType is a user-defined type, either a Table, View or Typedef.

Instances
Category Definition # 
Instance details

Defined in Squeal.PostgreSQL.Definition

Methods

id :: Definition a a #

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

(KnownSymbol alias, schema1 ~ ((alias ::: View cte) ': schema)) => Aliasable alias (statement schema params cte) (AlignedList (CommonTableExpression statement params) schema schema1) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query

Methods

as :: statement schema params cte -> Alias alias -> AlignedList (CommonTableExpression statement params) schema schema1 Source #

type SchemaType = [(Symbol, SchemumType)] Source #

The schema of a database consists of a list of aliased, user-defined SchemumTypes.

>>> :{
type family Schema :: SchemaType where
  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
        ])
    ]
:}

Constraints

type (:=>) constraint ty = '(constraint, ty) infixr 7 Source #

The constraint operator, :=> is a type level pair between a "constraint" and some type, for use in pairing a ColumnConstraint with a NullityType to produce a ColumnType or a TableConstraints and a ColumnsType to produce a TableType.

data ColumnConstraint Source #

ColumnConstraint encodes the availability of DEFAULT for inserts and updates. A column can be assigned a default value. A data Manipulation command can also request explicitly that a column be set to its default value, without having to know what that value is.

Constructors

Def

DEFAULT is available for inserts and updates

NoDef

DEFAULT is unavailable for inserts and updates

Instances
ty0 ~ ty1 => SamePGType (alias0 ::: (def0 :=> nullity0 ty0)) (alias1 ::: (def1 :=> nullity1 ty1)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

AddColumn (Def :=> ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition

Methods

addColumn :: (KnownSymbol column, Has tab schema (Table table0), table0 ~ (constraints :=> columns), table1 ~ (constraints :=> Create column (Def :=> ty) columns)) => Alias column -> ColumnTypeExpression schema (Def :=> ty) -> AlterTable tab table1 schema Source #

AddColumn (NoDef :=> Null ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition

Methods

addColumn :: (KnownSymbol column, Has tab schema (Table table0), table0 ~ (constraints :=> columns), table1 ~ (constraints :=> Create column (NoDef :=> Null ty) columns)) => Alias column -> ColumnTypeExpression schema (NoDef :=> Null ty) -> AlterTable tab table1 schema Source #

data TableConstraint Source #

TableConstraint encodes various forms of data constraints of columns in a table. 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.

type family Uniquely (key :: [Symbol]) (constraints :: TableConstraints) :: Constraint where ... Source #

A ForeignKey must reference columns that either are a PrimaryKey or form a Unique constraint.

Equations

Uniquely key ((uq ::: Unique key) ': constraints) = () 
Uniquely key ((pk ::: PrimaryKey key) ': constraints) = () 
Uniquely key (_ ': constraints) = Uniquely key constraints 

Aliases

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

The alias operator ::: is like a promoted version of As, a type level pair between an alias and some type.

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
IsQualified table column (Alias table, Alias column) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

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

alias1 ~ alias2 => IsLabel alias1 (Alias alias2) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

fromLabel :: Alias alias2 #

(alias0 ~ alias1, alias0 ~ alias2, KnownSymbol alias2) => IsLabel alias0 (Aliased Alias (alias1 ::: alias2)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

fromLabel :: Aliased Alias (alias1 ::: alias2) #

aliases ~ (alias ': ([] :: [Symbol])) => IsLabel alias (NP Alias aliases) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

fromLabel :: NP Alias aliases #

Eq (Alias alias) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

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

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

Ord (Alias alias) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

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 # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

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

show :: Alias alias -> String #

showList :: [Alias alias] -> ShowS #

Generic (Alias alias) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

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 # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

rnf :: Alias alias -> () #

KnownSymbol alias => RenderSQL (Alias alias) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

renderSQL :: Alias alias -> ByteString Source #

type Rep (Alias alias) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type Rep (Alias alias) = D1 (MetaData "Alias" "Squeal.PostgreSQL.Schema" "squeal-postgresql-0.4.0.0-GuxxUOwtUmZB6qL3MLEXvb" False) (C1 (MetaCons "Alias" PrefixI False) (U1 :: * -> *))

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

>>> renderAlias #jimbob
"\"jimbob\""

renderAliases :: All KnownSymbol aliases => NP Alias aliases -> [ByteString] Source #

>>> import Generics.SOP (NP(..))
>>> renderAliases (#jimbob :* #kandi)
["\"jimbob\"","\"kandi\""]

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
(Has table from columns, Has column columns ty, GroupedBy table column bys) => IsQualified table column (NP (Aliased (Expression schema from (Grouped bys) params)) ((column ::: ty) ': ([] :: [(Symbol, NullityType)]))) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(!) :: Alias table -> Alias column -> NP (Aliased (Expression schema from (Grouped bys) params)) ((column ::: ty) ': []) Source #

(Has table from columns, Has column columns ty, GroupedBy table column bys) => IsQualified table column (Aliased (Expression schema from (Grouped bys) params) (column ::: ty)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

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

(Has table from columns, Has column columns ty) => IsQualified table column (NP (Aliased (Expression schema from Ungrouped params)) ((column ::: ty) ': ([] :: [(Symbol, NullityType)]))) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(!) :: Alias table -> Alias column -> NP (Aliased (Expression schema from Ungrouped params)) ((column ::: ty) ': []) Source #

(Has table from columns, Has column columns ty) => IsQualified table column (Aliased (Expression schema from Ungrouped params) (column ::: ty)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(!) :: Alias table -> Alias column -> Aliased (Expression schema from Ungrouped params) (column ::: ty) Source #

(KnownSymbol alias, tys ~ ((alias ::: ty) ': ([] :: [(Symbol, k)]))) => Aliasable alias (expression ty) (NP (Aliased expression) tys) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

as :: expression ty -> Alias alias -> NP (Aliased expression) tys Source #

(KnownSymbol alias, alias ~ alias1) => Aliasable alias (expression ty) (Aliased expression (alias1 ::: ty)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

as :: expression ty -> Alias alias -> Aliased expression (alias1 ::: ty) Source #

(alias0 ~ alias1, alias0 ~ alias2, KnownSymbol alias2) => IsLabel alias0 (Aliased Alias (alias1 ::: alias2)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

fromLabel :: Aliased Alias (alias1 ::: alias2) #

(HasUnique table from columns, Has column columns ty, GroupedBy table column bys) => IsLabel column (NP (Aliased (Expression schema from (Grouped bys) params)) ((column ::: ty) ': ([] :: [(Symbol, NullityType)]))) # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: NP (Aliased (Expression schema from (Grouped bys) params)) ((column ::: ty) ': []) #

(HasUnique table from columns, Has column columns ty, GroupedBy table column bys) => IsLabel column (Aliased (Expression schema from (Grouped bys) params) (column ::: ty)) # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: Aliased (Expression schema from (Grouped bys) params) (column ::: ty) #

(HasUnique table from columns, Has column columns ty) => IsLabel column (NP (Aliased (Expression schema from Ungrouped params)) ((column ::: ty) ': ([] :: [(Symbol, NullityType)]))) # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: NP (Aliased (Expression schema from Ungrouped params)) ((column ::: ty) ': []) #

(HasUnique table from columns, Has column columns ty) => IsLabel column (Aliased (Expression schema from Ungrouped params) (column ::: ty)) # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: Aliased (Expression schema from Ungrouped params) (column ::: ty) #

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

Defined in Squeal.PostgreSQL.Schema

Methods

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

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

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

Defined in Squeal.PostgreSQL.Schema

Methods

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

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

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

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

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

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

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

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

Defined in Squeal.PostgreSQL.Schema

Methods

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

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

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

class KnownSymbol alias => Aliasable alias expression aliased | aliased -> expression, aliased -> alias where Source #

The Aliasable class provides a way to scrap your Nils in an NP list of Aliased expressions.

Minimal complete definition

as

Methods

as :: expression -> Alias alias -> aliased Source #

Instances
(KnownSymbol alias, tys ~ ((alias ::: ty) ': ([] :: [(Symbol, k)]))) => Aliasable alias (expression ty) (NP (Aliased expression) tys) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

as :: expression ty -> Alias alias -> NP (Aliased expression) tys Source #

(KnownSymbol alias, alias ~ alias1) => Aliasable alias (expression ty) (Aliased expression (alias1 ::: ty)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

as :: expression ty -> Alias alias -> Aliased expression (alias1 ::: ty) Source #

(KnownSymbol alias, schema1 ~ ((alias ::: View cte) ': schema)) => Aliasable alias (statement schema params cte) (AlignedList (CommonTableExpression statement params) schema schema1) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query

Methods

as :: statement schema params cte -> Alias alias -> AlignedList (CommonTableExpression statement params) schema schema1 Source #

(KnownSymbol alias, schema1 ~ ((alias ::: View cte) ': schema)) => Aliasable alias (statement schema params cte) (CommonTableExpression statement params schema schema1) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query

Methods

as :: statement schema params cte -> Alias alias -> CommonTableExpression statement params schema schema1 Source #

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

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

class KnownSymbol alias => Has (alias :: Symbol) (fields :: [(Symbol, kind)]) (field :: kind) | alias fields -> field Source #

Has alias fields field is a constraint that proves that fields has a field of alias ::: field, inferring field from alias and fields.

Instances
(KnownSymbol alias, Has alias fields field) => Has alias (field' ': fields :: [(Symbol, kind)]) (field :: kind) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

KnownSymbol alias => Has alias ((alias ::: field) ': fields :: [(Symbol, kind)]) (field :: kind) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

type HasUnique alias fields field = fields ~ '[alias ::: field] Source #

HasUnique alias fields field is a constraint that proves that fields is a singleton of alias ::: field.

class All KnownSymbol aliases => HasAll (aliases :: [Symbol]) (fields :: [(Symbol, kind)]) (subfields :: [(Symbol, kind)]) | aliases fields -> subfields Source #

HasAll extends Has to take lists of aliases and fields and infer a list of subfields.

Instances
HasAll ([] :: [Symbol]) (fields :: [(Symbol, kind)]) ([] :: [(Symbol, kind)]) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

(Has alias fields field, HasAll aliases fields subfields) => HasAll (alias ': aliases) (fields :: [(Symbol, k)]) ((alias ::: field) ': subfields :: [(Symbol, k)]) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

class IsLabel (x :: Symbol) a where #

Minimal complete definition

fromLabel

Methods

fromLabel :: a #

Instances
alias1 ~ alias2 => IsLabel alias1 (Alias alias2) # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

fromLabel :: Alias alias2 #

(HasUnique rel rels cols, Has col cols ty, by ~ (,) rel col) => IsLabel col (By rels by) # 
Instance details

Defined in Squeal.PostgreSQL.Query

Methods

fromLabel :: By rels by #

(alias0 ~ alias1, alias0 ~ alias2, KnownSymbol alias2) => IsLabel alias0 (Aliased Alias (alias1 ::: alias2)) # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

fromLabel :: Aliased Alias (alias1 ::: alias2) #

aliases ~ (alias ': ([] :: [Symbol])) => IsLabel alias (NP Alias aliases) # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

fromLabel :: NP Alias aliases #

(HasUnique table from columns, Has column columns ty, GroupedBy table column bys) => IsLabel column (NP (Aliased (Expression schema from (Grouped bys) params)) ((column ::: ty) ': ([] :: [(Symbol, NullityType)]))) # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: NP (Aliased (Expression schema from (Grouped bys) params)) ((column ::: ty) ': []) #

(HasUnique table from columns, Has column columns ty, GroupedBy table column bys) => IsLabel column (Aliased (Expression schema from (Grouped bys) params) (column ::: ty)) # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: Aliased (Expression schema from (Grouped bys) params) (column ::: ty) #

(HasUnique table from columns, Has column columns ty) => IsLabel column (NP (Aliased (Expression schema from Ungrouped params)) ((column ::: ty) ': ([] :: [(Symbol, NullityType)]))) # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: NP (Aliased (Expression schema from Ungrouped params)) ((column ::: ty) ': []) #

(HasUnique table from columns, Has column columns ty) => IsLabel column (Aliased (Expression schema from Ungrouped params) (column ::: ty)) # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: Aliased (Expression schema from Ungrouped params) (column ::: ty) #

(HasUnique rel rels cols, Has col cols ty, bys ~ ((,) rel col ': ([] :: [(Symbol, Symbol)]))) => IsLabel col (NP (By rels) bys) # 
Instance details

Defined in Squeal.PostgreSQL.Query

Methods

fromLabel :: NP (By rels) bys #

(HasUnique table from columns, Has column columns ty, GroupedBy table column bys) => IsLabel column (Expression schema from (Grouped bys) params ty) # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: Expression schema from (Grouped bys) params ty #

(HasUnique table from columns, Has column columns ty) => IsLabel column (Expression schema from Ungrouped params ty) # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: Expression schema from Ungrouped params ty #

class IsQualified table column expression where Source #

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

Minimal complete definition

(!)

Methods

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

Instances
IsQualified table column (Alias table, Alias column) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

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

(Has rel rels cols, Has col cols ty, by ~ (,) rel col) => IsQualified rel col (By rels by) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query

Methods

(!) :: Alias rel -> Alias col -> By rels by Source #

(Has table from columns, Has column columns ty, GroupedBy table column bys) => IsQualified table column (NP (Aliased (Expression schema from (Grouped bys) params)) ((column ::: ty) ': ([] :: [(Symbol, NullityType)]))) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(!) :: Alias table -> Alias column -> NP (Aliased (Expression schema from (Grouped bys) params)) ((column ::: ty) ': []) Source #

(Has table from columns, Has column columns ty, GroupedBy table column bys) => IsQualified table column (Aliased (Expression schema from (Grouped bys) params) (column ::: ty)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

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

(Has table from columns, Has column columns ty) => IsQualified table column (NP (Aliased (Expression schema from Ungrouped params)) ((column ::: ty) ': ([] :: [(Symbol, NullityType)]))) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(!) :: Alias table -> Alias column -> NP (Aliased (Expression schema from Ungrouped params)) ((column ::: ty) ': []) Source #

(Has table from columns, Has column columns ty) => IsQualified table column (Aliased (Expression schema from Ungrouped params) (column ::: ty)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(!) :: Alias table -> Alias column -> Aliased (Expression schema from Ungrouped params) (column ::: ty) Source #

(Has rel rels cols, Has col cols ty, bys ~ ((,) rel col ': ([] :: [(Symbol, Symbol)]))) => IsQualified rel col (NP (By rels) bys) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query

Methods

(!) :: Alias rel -> Alias col -> NP (By rels) bys Source #

(Has table from columns, Has column columns ty, GroupedBy table column bys) => IsQualified table column (Expression schema from (Grouped bys) params ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

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

(Has table from columns, Has column columns ty) => IsQualified table column (Expression schema from Ungrouped params ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

>>> renderAliasString #ohmahgerd
"'ohmahgerd'"

Enumerated Labels

class IsPGlabel (label :: Symbol) expr where Source #

IsPGlabel looks very much like the IsLabel class. Whereas the overloaded label, fromLabel is used for column references, labels are used for enum terms. A label is called with type application like `label @"beef"`.

Minimal complete definition

label

Methods

label :: expr Source #

Instances
label ~ label1 => IsPGlabel label (PGlabel label1) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

label :: PGlabel label1 Source #

labels ~ (label ': ([] :: [Symbol])) => IsPGlabel label (NP PGlabel labels) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

label :: NP PGlabel labels Source #

(KnownSymbol label, In label labels) => IsPGlabel label (Expression schema from grouping params (nullity (PGenum labels))) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

label :: Expression schema from grouping params (nullity (PGenum labels)) Source #

data PGlabel (label :: Symbol) Source #

A PGlabel unit type with an IsPGlabel instance

Constructors

PGlabel 
Instances
label ~ label1 => IsPGlabel label (PGlabel label1) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

label :: PGlabel label1 Source #

labels ~ (label ': ([] :: [Symbol])) => IsPGlabel label (NP PGlabel labels) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

label :: NP PGlabel labels Source #

renderLabel :: KnownSymbol label => proxy label -> ByteString Source #

Renders a label

renderLabels :: All KnownSymbol labels => NP PGlabel labels -> [ByteString] Source #

Renders a list of labels

type family LabelsPG (hask :: Type) :: [ConstructorName] where ... Source #

The LabelsPG type family calculates the constructors of a Haskell enum type.

>>> data Schwarma = Beef | Lamb | Chicken deriving GHC.Generic
>>> instance Generic Schwarma
>>> instance HasDatatypeInfo Schwarma
>>> :kind! LabelsPG Schwarma
LabelsPG Schwarma :: [Type.ConstructorName]
= '["Beef", "Lamb", "Chicken"]

Equations

LabelsPG hask = ConstructorNamesOf (ConstructorsOf (DatatypeInfoOf hask)) 

Grouping

data Grouping Source #

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

Constructors

Ungrouped

no aggregation permitted

Grouped [(Symbol, Symbol)]

aggregation required for any column which is not grouped

class (KnownSymbol table, KnownSymbol column) => GroupedBy table column bys Source #

A GroupedBy constraint indicates that a table qualified column is a member of the auxiliary namespace created by GROUP BY clauses and thus, may be called in an output Expression without aggregating.

Instances
(KnownSymbol table, KnownSymbol column) => GroupedBy table column ((,) table column ': bys :: [(Symbol, Symbol)]) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

(KnownSymbol table, KnownSymbol column, GroupedBy table column bys) => GroupedBy table column (tabcol ': bys :: [a]) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Aligned lists

data AlignedList p x0 x1 where Source #

An AlignedList is a type-aligned list or free category.

Constructors

Done :: AlignedList p x x 
(:>>) :: p x0 x1 -> AlignedList p x1 x2 -> AlignedList p x0 x2 infixr 7 
Instances
Category (AlignedList p :: k -> k -> *) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

id :: AlignedList p a a #

(.) :: AlignedList p b c -> AlignedList p a b -> AlignedList p a c #

(KnownSymbol alias, schema1 ~ ((alias ::: View cte) ': schema)) => Aliasable alias (statement schema params cte) (AlignedList (CommonTableExpression statement params) schema schema1) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query

Methods

as :: statement schema params cte -> Alias alias -> AlignedList (CommonTableExpression statement params) schema schema1 Source #

single :: p x0 x1 -> AlignedList p x0 x1 Source #

A single step.

Data Definitions

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 addColumn.

Equations

Create alias x '[] = '[alias ::: x] 
Create alias x ((alias ::: y) ': xs) = TypeError ((Text "Create: alias " :<>: ShowType alias) :<>: Text "already in use") 
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 x xs where ... Source #

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

Equations

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

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 

type family DropIfConstraintsInvolve column constraints where ... Source #

Drop all TableConstraints that involve a column

Equations

DropIfConstraintsInvolve column '[] = '[] 
DropIfConstraintsInvolve column ((alias ::: constraint) ': constraints) = If (ConstraintInvolves column constraint) (DropIfConstraintsInvolve column constraints) ((alias ::: constraint) ': DropIfConstraintsInvolve column constraints) 

Lists

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 Elem x xs where ... Source #

Elem is a promoted elem.

Equations

Elem x '[] = False 
Elem x (x ': xs) = True 
Elem x (_ ': xs) = Elem x xs 

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

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

Equations

In x xs = Elem x xs ~ True 

type family Length (xs :: [k]) :: Nat where ... Source #

Calculate the Length of a type level list

>>> :kind! Length '[Char,String,Bool,Double]
Length '[Char,String,Bool,Double] :: Nat
= 4

Equations

Length (x ': xs) = 1 + Length xs 
Length '[] = 0 

Type Classifications

class HasOid (ty :: PGType) where Source #

The object identifier of a PGType.

>>> :set -XTypeApplications
>>> oid @'PGbool
16

Minimal complete definition

oid

Methods

oid :: Word32 Source #

Instances
HasOid PGbool Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

oid :: Word32 Source #

HasOid PGint2 Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

oid :: Word32 Source #

HasOid PGint4 Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

oid :: Word32 Source #

HasOid PGint8 Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

oid :: Word32 Source #

HasOid PGnumeric Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

oid :: Word32 Source #

HasOid PGfloat4 Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

oid :: Word32 Source #

HasOid PGfloat8 Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

oid :: Word32 Source #

HasOid PGtext Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

oid :: Word32 Source #

HasOid PGbytea Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

oid :: Word32 Source #

HasOid PGtimestamp Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

oid :: Word32 Source #

HasOid PGtimestamptz Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

oid :: Word32 Source #

HasOid PGdate Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

oid :: Word32 Source #

HasOid PGtime Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

oid :: Word32 Source #

HasOid PGtimetz Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

oid :: Word32 Source #

HasOid PGinterval Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

oid :: Word32 Source #

HasOid PGuuid Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

oid :: Word32 Source #

HasOid PGinet Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

oid :: Word32 Source #

HasOid PGjson Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

oid :: Word32 Source #

HasOid PGjsonb Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

oid :: Word32 Source #

HasOid (PGchar n) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

oid :: Word32 Source #

HasOid (PGvarchar n) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

oid :: Word32 Source #

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

Numeric Postgres types.

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

Integral Postgres types.

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

Floating Postgres types.

type family PGTypeOf (ty :: NullityType) :: PGType where ... Source #

PGTypeOf forgets about NULL and any column constraints.

Equations

PGTypeOf (nullity pg) = pg 

type family PGArrayOf name arr ty :: Constraint where ... Source #

Ensure a type is a valid array type with a specific element type.

Equations

PGArrayOf name (PGvararray x) ty = x ~ ty 
PGArrayOf name (PGfixarray n x) ty = x ~ ty 
PGArrayOf name val ty = TypeError ((((Text name :<>: Text "Unsatisfied PGArrayOf constraint. Expected either: ") :$$: (Text " \8226 " :<>: ErrPGvararrayOf (ShowType ty))) :$$: (Text " \8226 " :<>: ErrPGfixarrayOf (ShowType ty))) :$$: (Text "But got: " :<>: ShowType val)) 

type family PGArray name arr :: Constraint where ... Source #

Ensure a type is a valid array type.

Equations

PGArray name (PGvararray x) = () 
PGArray name (PGfixarray n x) = () 
PGArray name val = TypeError ((((Text name :<>: Text ": Unsatisfied PGArray constraint. Expected either: ") :$$: (Text " \8226 " :<>: ErrPGvararrayOf (Placeholder PGType))) :$$: (Text " \8226 " :<>: ErrPGfixarrayOf (Placeholder PGType))) :$$: (Text "But got: " :<>: ShowType val)) 

type PGTextArray name arr = PGArrayOf name arr (NotNull PGtext) Source #

Ensure a type is a valid array type whose elements are text.

type PGJsonType = '[PGjson, PGjsonb] Source #

Is a type a valid JSON type?

type PGJsonKey = '[PGint2, PGint4, PGtext] Source #

Is a type a valid JSON key?

class SamePGType (ty0 :: (Symbol, ColumnType)) (ty1 :: (Symbol, ColumnType)) Source #

Equality constraint on the underlying PGType of two columns.

Instances
ty0 ~ ty1 => SamePGType (alias0 ::: (def0 :=> nullity0 ty0)) (alias1 ::: (def1 :=> nullity1 ty1)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

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

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

Equations

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

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

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

Equations

NotAllNull ((column ::: (def :=> NotNull ty)) ': columns) = () 
NotAllNull ((column ::: (def :=> Null ty)) ': columns) = NotAllNull columns 

Nullifications

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

NullifyType is an idempotent that nullifies a NullityType.

Equations

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

type family NullifyRow (columns :: RowType) :: RowType where ... Source #

NullifyRow is an idempotent that nullifies a RowType.

Equations

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

type family NullifyFrom (tables :: FromType) :: FromType where ... Source #

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

Equations

NullifyFrom '[] = '[] 
NullifyFrom ((table ::: columns) ': tables) = (table ::: NullifyRow columns) ': NullifyFrom tables 

Table Conversions

type family TableToColumns (table :: TableType) :: ColumnsType where ... Source #

TableToColumns removes table constraints.

Equations

TableToColumns (constraints :=> columns) = columns 

type family TableToRow (table :: TableType) :: RowType where ... Source #

Convert a table to a row type.

Equations

TableToRow tab = ColumnsToRow (TableToColumns tab)