Copyright | (c) Eitan Chatav 2019 |
---|---|
Maintainer | eitan@morphism.tech |
Stability | experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Provides a type-level DSL for kinds of Postgres types, tables, schema, constraints, and more. It also defines useful type families to operate on these.
Synopsis
- data PGType
- = PGbool
- | PGint2
- | PGint4
- | PGint8
- | PGnumeric
- | PGfloat4
- | PGfloat8
- | PGmoney
- | PGchar Nat
- | PGvarchar Nat
- | PGtext
- | PGbytea
- | PGtimestamp
- | PGtimestamptz
- | PGdate
- | PGtime
- | PGtimetz
- | PGinterval
- | PGuuid
- | PGinet
- | PGjson
- | PGjsonb
- | PGvararray NullType
- | PGfixarray [Nat] NullType
- | PGenum [Symbol]
- | PGcomposite RowType
- | PGtsvector
- | PGtsquery
- | PGoid
- | PGrange PGType
- | UnsafePGType Symbol
- data NullType
- type RowType = [(Symbol, NullType)]
- type FromType = [(Symbol, RowType)]
- type ColumnType = (Optionality, NullType)
- type ColumnsType = [(Symbol, ColumnType)]
- type TableType = (TableConstraints, ColumnsType)
- data SchemumType
- data IndexType
- type FunctionType = ([NullType], ReturnsType)
- data ReturnsType
- type SchemaType = [(Symbol, SchemumType)]
- type SchemasType = [(Symbol, SchemaType)]
- type family Public (schema :: SchemaType) :: SchemasType where ...
- type family SubDB (db0 :: SchemasType) (db1 :: SchemasType) :: Bool where ...
- type family SubsetDB (db0 :: SchemasType) (db1 :: SchemasType) :: Bool where ...
- type family ElemDB (sch :: (Symbol, SchemaType)) (db :: SchemasType) :: Bool where ...
- type (:=>) constraint ty = '(constraint, ty)
- data Optionality
- data TableConstraint
- type TableConstraints = [(Symbol, TableConstraint)]
- type family Uniquely (key :: [Symbol]) (constraints :: TableConstraints) :: Constraint where ...
- class IsPGlabel (label :: Symbol) expr where
- label :: expr
- data PGlabel (label :: Symbol) = PGlabel
- type family Create alias x xs where ...
- type family CreateIfNotExists alias x xs where ...
- type family CreateOrReplace alias x xs where ...
- type family Drop alias xs where ...
- type family DropSchemum alias sch xs where ...
- type family DropIfExists alias xs where ...
- type family DropSchemumIfExists alias sch xs where ...
- type family Alter alias x xs where ...
- type family AlterIfExists alias x xs where ...
- type family Rename alias0 alias1 xs where ...
- type family RenameIfExists alias0 alias1 xs where ...
- type family SetSchema sch0 sch1 schema0 schema1 obj srt ty db where ...
- type family ConstraintInvolves column constraint where ...
- type family DropIfConstraintsInvolve column constraints where ...
- type PGNum = '['PGint2, 'PGint4, 'PGint8, 'PGnumeric, 'PGfloat4, 'PGfloat8]
- type PGIntegral = '['PGint2, 'PGint4, 'PGint8]
- type PGFloating = '['PGfloat4, 'PGfloat8, 'PGnumeric]
- type PGJsonType = '['PGjson, 'PGjsonb]
- type PGJsonKey = '['PGint2, 'PGint4, 'PGtext]
- class SamePGType (ty0 :: (Symbol, ColumnType)) (ty1 :: (Symbol, ColumnType))
- type family AllNotNull (columns :: ColumnsType) :: Constraint where ...
- type family NotAllNull (columns :: ColumnsType) :: Constraint where ...
- type family NullifyType (ty :: NullType) :: NullType where ...
- type family NullifyRow (columns :: RowType) :: RowType where ...
- type family NullifyFrom (tables :: FromType) :: FromType where ...
- type family TableToColumns (table :: TableType) :: ColumnsType where ...
- type family ColumnsToRow (columns :: ColumnsType) :: RowType where ...
- type family TableToRow (table :: TableType) :: RowType where ...
- type Updatable table columns = (All (HasIn (TableToColumns table)) columns, AllUnique columns, SListI (TableToColumns table))
- class AllUnique (xs :: [(Symbol, a)])
- class IsNotElem x isElem
- type family DbEnums db where ...
- type family SchemaEnums schema where ...
- type family DbRelations db where ...
- type family SchemaRelations schema where ...
- type family FindQualified err xss x where ...
- type family FindName xs x where ...
- type family FindNamespace err nsp name xss x where ...
- type family PrettyPrintPartitionedSchema (schema :: PartitionedSchema) :: ErrorMessage where ...
- data PartitionedSchema = PartitionedSchema {}
- type PartitionSchema schema = PartitionSchema' schema ('PartitionedSchema '[] '[] '[] '[] '[] '[] '[])
- type family SchemaFunctions (schema :: PartitionedSchema) :: [(Symbol, FunctionType)] where ...
- type family SchemaIndexes (schema :: PartitionedSchema) :: [(Symbol, IndexType)] where ...
- type family SchemaProcedures (schema :: PartitionedSchema) :: [(Symbol, [NullType])] where ...
- type family SchemaTables (schema :: PartitionedSchema) :: [(Symbol, TableType)] where ...
- type family SchemaTypes (schema :: PartitionedSchema) :: [(Symbol, PGType)] where ...
- type family SchemaUnsafes (schema :: PartitionedSchema) :: [(Symbol, Symbol)] where ...
- type family SchemaViews (schema :: PartitionedSchema) :: [(Symbol, RowType)] where ...
- type family IntersperseNewlines (ls :: [ErrorMessage]) :: ErrorMessage where ...
- type family FilterNonEmpty (ls :: [ErrorMessage]) :: [ErrorMessage] where ...
- type family FieldIfNonEmpty (fieldName :: Symbol) (value :: [(Symbol, k)]) :: ErrorMessage where ...
- type family PartitionSchema' (remaining :: SchemaType) (acc :: PartitionedSchema) :: PartitionedSchema where ...
Postgres Type
PGType
is the promoted datakind of PostgreSQL types.
>>>
:kind 'PGbool
'PGbool :: PGType
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) |
PGmoney | currency amount |
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 NullType | variable length array |
PGfixarray [Nat] NullType | 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. |
PGtsvector | A tsvector value is a sorted list of distinct lexemes, which are words that have been normalized to merge different variants of the same word. |
PGtsquery | A tsquery value stores lexemes that are to be searched for. |
PGoid | Object identifiers (OIDs) are used internally by PostgreSQL as primary keys for various system tables. |
PGrange PGType | Range types are data types representing a range of values of some element type (called the range's subtype). |
UnsafePGType Symbol | an escape hatch for unsupported PostgreSQL types |
Instances
NullType
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 :: NullType>>>
:kind 'NotNull ('PGvarchar 50)
'NotNull ('PGvarchar 50) :: NullType
Instances
Aggregate AggregateArg (Expression ('Grouped bys) :: FromType -> FromType -> SchemasType -> [NullType] -> FromType -> NullType -> Type) Source # | |
Defined in Squeal.PostgreSQL.Expression.Aggregate countStar :: forall (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). Expression ('Grouped bys) lat with db params from ('NotNull 'PGint8) Source # count :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('NotNull 'PGint8) Source # sum_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGSum ty)) Source # arrayAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null ('PGvararray ty)) Source # jsonAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGjson) Source # jsonbAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGjsonb) Source # bitAnd :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => AggregateArg '[null int] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null int) Source # bitOr :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => AggregateArg '[null int] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null int) Source # boolAnd :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGbool] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGbool) Source # boolOr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGbool] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGbool) Source # every :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGbool] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGbool) Source # max_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null ty) Source # min_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null ty) Source # avg :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source # corr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # covarPop :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # covarSamp :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrAvgX :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrAvgY :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrCount :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGint8) Source # regrIntercept :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrR2 :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrSlope :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrSxx :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrSxy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrSyy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # stddev :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source # stddevPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source # stddevSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source # variance :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source # varPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source # varSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source # | |
(TypeError ('Text "Cannot use aggregate functions to construct an Ungrouped Expression. Add a 'groupBy' to your TableExpression. If you want to aggregate across the entire result set, use 'groupBy Nil'.") :: Constraint, a ~ AggregateArg) => Aggregate (a :: [NullType] -> FromType -> FromType -> SchemasType -> [NullType] -> FromType -> Type) (Expression 'Ungrouped) Source # | |
Defined in Squeal.PostgreSQL.Expression.Aggregate countStar :: forall (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). Expression 'Ungrouped lat with db params from ('NotNull 'PGint8) Source # count :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('NotNull 'PGint8) Source # sum_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null (PGSum ty)) Source # arrayAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null ('PGvararray ty)) Source # jsonAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGjson) Source # jsonbAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGjsonb) Source # bitAnd :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => a '[null int] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null int) Source # bitOr :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => a '[null int] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null int) Source # boolAnd :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGbool] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGbool) Source # boolOr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGbool] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGbool) Source # every :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGbool] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGbool) Source # max_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null ty) Source # min_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null ty) Source # avg :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty)) Source # corr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # covarPop :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # covarSamp :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # regrAvgX :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # regrAvgY :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # regrCount :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGint8) Source # regrIntercept :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # regrR2 :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # regrSlope :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # regrSxx :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # regrSxy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # regrSyy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # stddev :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty)) Source # stddevPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty)) Source # stddevSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty)) Source # variance :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty)) Source # varPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty)) Source # varSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty)) Source # | |
Aggregate (WindowArg grp :: [NullType] -> FromType -> FromType -> SchemasType -> [NullType] -> FromType -> Type) (WindowFunction grp :: FromType -> FromType -> SchemasType -> [NullType] -> FromType -> NullType -> TYPE LiftedRep) Source # | |
Defined in Squeal.PostgreSQL.Expression.Window countStar :: forall (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowFunction grp lat with db params from ('NotNull 'PGint8) Source # count :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[ty] lat with db params from -> WindowFunction grp lat with db params from ('NotNull 'PGint8) Source # sum_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGSum ty)) Source # arrayAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[ty] lat with db params from -> WindowFunction grp lat with db params from ('Null ('PGvararray ty)) Source # jsonAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[ty] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGjson) Source # jsonbAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[ty] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGjsonb) Source # bitAnd :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => WindowArg grp '[null int] lat with db params from -> WindowFunction grp lat with db params from ('Null int) Source # bitOr :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => WindowArg grp '[null int] lat with db params from -> WindowFunction grp lat with db params from ('Null int) Source # boolAnd :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGbool] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGbool) Source # boolOr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGbool] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGbool) Source # every :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGbool] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGbool) Source # max_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null ty) Source # min_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null ty) Source # avg :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source # corr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # covarPop :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # covarSamp :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # regrAvgX :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # regrAvgY :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # regrCount :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGint8) Source # regrIntercept :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # regrR2 :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # regrSlope :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # regrSxx :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # regrSxy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # regrSyy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # stddev :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source # stddevPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source # stddevSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source # variance :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source # varPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source # varSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source # | |
(Has tab (Join from lat) row, Has col row ty, GroupedBy tab col bys, tys ~ '[ty]) => IsQualified tab col (NP (Expression ('Grouped bys) lat with db params from) tys) Source # | |
Defined in Squeal.PostgreSQL.Expression | |
(Has tab (Join from lat) row, Has col row ty, tys ~ '[ty]) => IsQualified tab col (NP (Expression 'Ungrouped lat with db params from) tys) Source # | |
Defined in Squeal.PostgreSQL.Expression | |
(Has tab (Join from lat) row, Has col row ty, GroupedBy tab col bys, columns ~ '[col ::: ty]) => IsQualified tab col (NP (Aliased (Expression ('Grouped bys) lat with db params from)) columns) Source # | |
Defined in Squeal.PostgreSQL.Expression | |
(Has tab (Join from lat) row, Has col row ty, columns ~ '[col ::: ty]) => IsQualified tab col (NP (Aliased (Expression 'Ungrouped lat with db params from)) columns) Source # | |
Defined in Squeal.PostgreSQL.Expression | |
(Has tab (Join from lat) row, Has col row ty, GroupedBy tab col bys, column ~ (col ::: ty)) => IsQualified tab col (Aliased (Expression ('Grouped bys) lat with db params from) column) Source # | |
Defined in Squeal.PostgreSQL.Expression | |
(Has tab (Join from lat) row, Has col row ty, column ~ (col ::: ty)) => IsQualified tab col (Aliased (Expression 'Ungrouped lat with db params from) column) Source # | |
Defined in Squeal.PostgreSQL.Expression | |
(Has tab (Join from lat) row, Has col row ty) => IsQualified tab col (AggregateArg '[ty] lat with db params from) Source # | |
Defined in Squeal.PostgreSQL.Expression.Aggregate | |
(Has tab (Join from lat) row, Has col row ty, GroupedBy tab col bys) => IsQualified tab col (WindowArg ('Grouped bys) '[ty] lat with db params from) Source # | |
(Has tab (Join from lat) row, Has col row ty) => IsQualified tab col (WindowArg 'Ungrouped '[ty] lat with db params from) Source # | |
(KnownSymbol fld, FromValue ty y) => IsLabel fld (DecodeRow ((fld ::: ty) ': row) y) Source # | |
Defined in Squeal.PostgreSQL.Session.Decode | |
IsLabel fld (DecodeRow row y) => IsLabel fld (DecodeRow (field ': row) y) Source # | |
Defined in Squeal.PostgreSQL.Session.Decode | |
(KnownSymbol fld, FromValue ty (Maybe y)) => IsLabel fld (MaybeT (DecodeRow ((fld ::: ty) ': row)) y) Source # | |
IsLabel fld (MaybeT (DecodeRow row) y) => IsLabel fld (MaybeT (DecodeRow (field ': row)) y) Source # | |
Defined in Squeal.PostgreSQL.Session.Decode | |
(HasUnique tab (Join from lat) row, Has col row ty, GroupedBy tab col bys, tys ~ '[ty]) => IsLabel col (NP (Expression ('Grouped bys) lat with db params from) tys) Source # | |
Defined in Squeal.PostgreSQL.Expression fromLabel :: NP (Expression ('Grouped bys) lat with db params from) tys # | |
(HasUnique tab (Join from lat) row, Has col row ty, tys ~ '[ty]) => IsLabel col (NP (Expression 'Ungrouped lat with db params from) tys) Source # | |
Defined in Squeal.PostgreSQL.Expression fromLabel :: NP (Expression 'Ungrouped lat with db params from) tys # | |
(HasUnique tab (Join from lat) row, Has col row ty, GroupedBy tab col bys, columns ~ '[col ::: ty]) => IsLabel col (NP (Aliased (Expression ('Grouped bys) lat with db params from)) columns) Source # | |
Defined in Squeal.PostgreSQL.Expression | |
(HasUnique tab (Join from lat) row, Has col row ty, columns ~ '[col ::: ty]) => IsLabel col (NP (Aliased (Expression 'Ungrouped lat with db params from)) columns) Source # | |
Defined in Squeal.PostgreSQL.Expression | |
(HasUnique tab (Join from lat) row, Has col row ty, GroupedBy tab col bys, column ~ (col ::: ty)) => IsLabel col (Aliased (Expression ('Grouped bys) lat with db params from) column) Source # | |
Defined in Squeal.PostgreSQL.Expression fromLabel :: Aliased (Expression ('Grouped bys) lat with db params from) column # | |
(HasUnique tab (Join from lat) row, Has col row ty, column ~ (col ::: ty)) => IsLabel col (Aliased (Expression 'Ungrouped lat with db params from) column) Source # | |
Defined in Squeal.PostgreSQL.Expression fromLabel :: Aliased (Expression 'Ungrouped lat with db params from) column # | |
(KnownSymbol alias, NullTyped db ty) => FieldTyped db (alias ::: ty) Source # | |
Defined in Squeal.PostgreSQL.Expression.Type | |
OidOfNull db ty => OidOfField db (fld ::: ty) Source # | |
Defined in Squeal.PostgreSQL.Session.Oid oidOfField :: ReaderT (K Connection db) IO Oid Source # | |
(fld0 ~ fld1, ToParam db ty x) => ToField db (fld0 ::: ty) (fld1 ::: x) Source # | |
(ToParam db ty x, ty ~ NullPG x) => IsLabel fld (EncodeParams db '[fld ::: ty] x) Source # | |
Defined in Squeal.PostgreSQL.Session.Encode fromLabel :: EncodeParams db '[fld ::: ty] x # | |
NullTyped db ('NotNull ty) => ColumnTyped db ('NoDef :=> 'NotNull ty) Source # | |
Defined in Squeal.PostgreSQL.Expression.Type columntype :: ColumnTypeExpression db ('NoDef :=> 'NotNull ty) Source # | |
NullTyped db ('Null ty) => ColumnTyped db ('NoDef :=> 'Null ty) Source # | |
Defined in Squeal.PostgreSQL.Expression.Type columntype :: ColumnTypeExpression db ('NoDef :=> 'Null ty) Source # | |
(KnownSymbol cte, with1 ~ ((cte ::: common) ': with)) => Aliasable cte (statement with db params common) (Path (CommonTableExpression statement db params) with with1) Source # | |
Defined in Squeal.PostgreSQL.Query.With | |
(HasUnique tab (Join from lat) row, Has col row ty) => IsLabel col (AggregateArg '[ty] lat with db params from) Source # | |
Defined in Squeal.PostgreSQL.Expression.Aggregate fromLabel :: AggregateArg '[ty] lat with db params from # | |
(HasUnique tab (Join from lat) row, Has col row ty, GroupedBy tab col bys) => IsLabel col (WindowArg ('Grouped bys) '[ty] lat with db params from) Source # | |
Defined in Squeal.PostgreSQL.Expression.Window | |
(HasUnique tab (Join from lat) row, Has col row ty) => IsLabel col (WindowArg 'Ungrouped '[ty] lat with db params from) Source # | |
Defined in Squeal.PostgreSQL.Expression.Window | |
JsonBuildObject ('[] :: [NullType]) Source # | |
Defined in Squeal.PostgreSQL.Expression.Json | |
FilterWhere AggregateArg 'Ungrouped Source # | |
Defined in Squeal.PostgreSQL.Expression.Aggregate filterWhere :: forall (lat :: FromType) (with :: FromType) (db :: SchemasType) (params :: [NullType]) (from :: FromType) (xs :: k). Condition 'Ungrouped lat with db params from -> AggregateArg xs lat with db params from -> AggregateArg xs lat with db params from Source # | |
FilterWhere (WindowArg grp :: [NullType] -> FromType -> FromType -> SchemasType -> [NullType] -> FromType -> Type) grp Source # | |
Defined in Squeal.PostgreSQL.Expression.Window | |
Additional (FromClause lat with db params :: FromType -> Type) Source # | |
Defined in Squeal.PostgreSQL.Query.From also :: forall (ys :: [a]) (xs :: [a]). FromClause lat with db params ys -> FromClause lat with db params xs -> FromClause lat with db params (Join xs ys) Source # | |
Additional (Selection grp lat with db params from :: [(Symbol, NullType)] -> Type) Source # | |
(JsonBuildObject tys, In key PGJsonKey) => JsonBuildObject ('NotNull key ': (value ': tys)) Source # | |
FromValue ty y => FromAliasedValue (fld ::: ty) y Source # | |
Defined in Squeal.PostgreSQL.Session.Decode fromAliasedValue :: Maybe ByteString -> Either Text y Source # | |
(KnownSymbol col, InlineParam x ty) => InlineColumn (col ::: Optional I ('Def :=> x)) (col ::: ('Def :=> ty)) Source # | |
Defined in Squeal.PostgreSQL.Expression.Inline | |
(KnownSymbol col, InlineParam x ty) => InlineColumn (col ::: x) (col ::: ('NoDef :=> ty)) Source # | |
Defined in Squeal.PostgreSQL.Expression.Inline | |
(KnownSymbol alias, InlineParam x ty) => InlineField (alias ::: x) (alias ::: ty) Source # | |
Defined in Squeal.PostgreSQL.Expression.Inline inlineField :: forall (grp :: Grouping) (lat :: FromType) (with :: FromType) (db :: SchemasType) (params :: [NullType]) (from :: FromType). P (alias ::: x) -> Aliased (Expression grp lat with db params from) (alias ::: ty) Source # | |
(FromValue ty y, fld0 ~ fld1) => FromField (fld0 ::: ty) (fld1 ::: y) Source # | |
Defined in Squeal.PostgreSQL.Session.Decode | |
ty0 ~ ty1 => SamePGType (alias0 ::: (def0 :=> null0 ty0)) (alias1 ::: (def1 :=> null1 ty1)) Source # | |
Defined in Squeal.PostgreSQL.Type.Schema | |
AddColumn ('Def :=> ty) Source # | |
Defined in Squeal.PostgreSQL.Definition.Table addColumn :: forall (column :: Symbol) (sch :: Symbol) (db :: [(Symbol, [(Symbol, SchemumType)])]) (schema :: [(Symbol, SchemumType)]) (tab :: Symbol) (constraints :: TableConstraints) (columns :: ColumnsType). (KnownSymbol column, Has sch db schema, Has tab schema ('Table (constraints :=> columns))) => Alias column -> ColumnTypeExpression db ('Def :=> ty) -> AlterTable sch tab db (constraints :=> Create column ('Def :=> ty) columns) Source # | |
AddColumn ('NoDef :=> 'Null ty) Source # | |
Defined in Squeal.PostgreSQL.Definition.Table addColumn :: forall (column :: Symbol) (sch :: Symbol) (db :: [(Symbol, [(Symbol, SchemumType)])]) (schema :: [(Symbol, SchemumType)]) (tab :: Symbol) (constraints :: TableConstraints) (columns :: ColumnsType). (KnownSymbol column, Has sch db schema, Has tab schema ('Table (constraints :=> columns))) => Alias column -> ColumnTypeExpression db ('NoDef :=> 'Null ty) -> AlterTable sch tab db (constraints :=> Create column ('NoDef :=> 'Null ty) columns) Source # | |
IsString (Selection grp lat with db params from '["fromOnly" ::: 'NotNull 'PGtext]) Source # | |
Defined in Squeal.PostgreSQL.Query.Select | |
type PrettyPrintHaystack (haystack :: ColumnsType) Source # | |
Defined in Squeal.PostgreSQL.Type.Schema type PrettyPrintHaystack (haystack :: ColumnsType) = 'PrettyPrintInfo ('Text "column definition (ColumnType)") ('Text "table (ColumnsType)") ('ShowType (Sort (MapFst haystack))) | |
type PrettyPrintHaystack (haystack :: RowType) Source # | |
Defined in Squeal.PostgreSQL.Type.Schema type PrettyPrintHaystack (haystack :: RowType) = 'PrettyPrintInfo ('Text "column (NullType)") ('Text "row (RowType)") ('ShowType (Sort (MapFst haystack))) | |
type PrettyPrintHaystack (haystack :: FromType) Source # | |
Defined in Squeal.PostgreSQL.Type.Schema type PrettyPrintHaystack (haystack :: FromType) = 'PrettyPrintInfo ('Text "row (RowType)") ('Text "from clause (FromType)") ('ShowType (Sort (MapFst haystack))) |
type FromType = [(Symbol, RowType)] Source #
FromType
is a row of RowType
s. It can be thought of as
a product, or horizontal gluing and is used in FromClause
s
and TableExpression
s.
Schema Type
type ColumnType = (Optionality, NullType) Source #
ColumnType
encodes the allowance of DEFAULT
and NULL
and the
base PGType
for a column.
>>>
:set -XTypeFamilies -XDataKinds -XPolyKinds
>>>
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 ColumnType
s.
>>>
:{
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-created type, like a Table
,
View
or Typedef
.
Table TableType | |
View RowType | |
Typedef PGType | |
Index IndexType | |
Function FunctionType | |
Procedure [NullType] | |
UnsafeSchemum Symbol |
Instances
Category Definition Source # | |
Defined in Squeal.PostgreSQL.Definition id :: forall (a :: k). Definition a a # (.) :: forall (b :: k) (c :: k) (a :: k). Definition b c -> Definition a b -> Definition a c # | |
IndexedMonadTrans PQ Source # | |
Defined in Squeal.PostgreSQL.Session pqAp :: forall (m :: Type -> Type) (i :: k) (j :: k) x y (k :: k). Monad m => PQ i j m (x -> y) -> PQ j k m x -> PQ i k m y Source # pqJoin :: forall (m :: Type -> Type) (i :: k) (j :: k) (k :: k) y. Monad m => PQ i j m (PQ j k m y) -> PQ i k m y Source # pqBind :: forall (m :: Type -> Type) x (j :: k) (k :: k) y (i :: k). Monad m => (x -> PQ j k m y) -> PQ i j m x -> PQ i k m y Source # pqThen :: forall (m :: Type -> Type) (j :: k) (k :: k) y (i :: k) x. Monad m => PQ j k m y -> PQ i j m x -> PQ i k m y Source # pqAndThen :: forall (m :: Type -> Type) y (j :: k) (k :: k) z x (i :: k). Monad m => (y -> PQ j k m z) -> (x -> PQ i j m y) -> x -> PQ i k m z Source # | |
Aggregate AggregateArg (Expression ('Grouped bys) :: FromType -> FromType -> SchemasType -> [NullType] -> FromType -> NullType -> Type) Source # | |
Defined in Squeal.PostgreSQL.Expression.Aggregate countStar :: forall (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). Expression ('Grouped bys) lat with db params from ('NotNull 'PGint8) Source # count :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('NotNull 'PGint8) Source # sum_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGSum ty)) Source # arrayAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null ('PGvararray ty)) Source # jsonAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGjson) Source # jsonbAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGjsonb) Source # bitAnd :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => AggregateArg '[null int] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null int) Source # bitOr :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => AggregateArg '[null int] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null int) Source # boolAnd :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGbool] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGbool) Source # boolOr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGbool] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGbool) Source # every :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGbool] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGbool) Source # max_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null ty) Source # min_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null ty) Source # avg :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source # corr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # covarPop :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # covarSamp :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrAvgX :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrAvgY :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrCount :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGint8) Source # regrIntercept :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrR2 :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrSlope :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrSxx :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrSxy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrSyy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # stddev :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source # stddevPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source # stddevSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source # variance :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source # varPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source # varSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source # | |
(TypeError ('Text "Cannot use aggregate functions to construct an Ungrouped Expression. Add a 'groupBy' to your TableExpression. If you want to aggregate across the entire result set, use 'groupBy Nil'.") :: Constraint, a ~ AggregateArg) => Aggregate (a :: [NullType] -> FromType -> FromType -> SchemasType -> [NullType] -> FromType -> Type) (Expression 'Ungrouped) Source # | |
Defined in Squeal.PostgreSQL.Expression.Aggregate countStar :: forall (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). Expression 'Ungrouped lat with db params from ('NotNull 'PGint8) Source # count :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('NotNull 'PGint8) Source # sum_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null (PGSum ty)) Source # arrayAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null ('PGvararray ty)) Source # jsonAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGjson) Source # jsonbAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGjsonb) Source # bitAnd :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => a '[null int] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null int) Source # bitOr :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => a '[null int] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null int) Source # boolAnd :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGbool] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGbool) Source # boolOr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGbool] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGbool) Source # every :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGbool] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGbool) Source # max_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null ty) Source # min_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null ty) Source # avg :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty)) Source # corr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # covarPop :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # covarSamp :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # regrAvgX :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # regrAvgY :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # regrCount :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGint8) Source # regrIntercept :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # regrR2 :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # regrSlope :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # regrSxx :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # regrSxy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # regrSyy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # stddev :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty)) Source # stddevPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty)) Source # stddevSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty)) Source # variance :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty)) Source # varPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty)) Source # varSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty)) Source # | |
Aggregate (WindowArg grp :: [NullType] -> FromType -> FromType -> SchemasType -> [NullType] -> FromType -> Type) (WindowFunction grp :: FromType -> FromType -> SchemasType -> [NullType] -> FromType -> NullType -> TYPE LiftedRep) Source # | |
Defined in Squeal.PostgreSQL.Expression.Window countStar :: forall (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowFunction grp lat with db params from ('NotNull 'PGint8) Source # count :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[ty] lat with db params from -> WindowFunction grp lat with db params from ('NotNull 'PGint8) Source # sum_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGSum ty)) Source # arrayAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[ty] lat with db params from -> WindowFunction grp lat with db params from ('Null ('PGvararray ty)) Source # jsonAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[ty] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGjson) Source # jsonbAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[ty] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGjsonb) Source # bitAnd :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => WindowArg grp '[null int] lat with db params from -> WindowFunction grp lat with db params from ('Null int) Source # bitOr :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => WindowArg grp '[null int] lat with db params from -> WindowFunction grp lat with db params from ('Null int) Source # boolAnd :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGbool] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGbool) Source # boolOr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGbool] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGbool) Source # every :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGbool] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGbool) Source # max_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null ty) Source # min_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null ty) Source # avg :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source # corr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # covarPop :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # covarSamp :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # regrAvgX :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # regrAvgY :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # regrCount :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGint8) Source # regrIntercept :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # regrR2 :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # regrSlope :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # regrSxx :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # regrSxy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # regrSyy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # stddev :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source # stddevPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source # stddevSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source # variance :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source # varPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source # varSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source # | |
Migratory Definition (Indexed PQ IO ()) Source # | pure migrations |
Defined in Squeal.PostgreSQL.Session.Migration runMigrations :: forall (db0 :: k) (db1 :: k). Path (Migration Definition) db0 db1 -> Indexed PQ IO () db0 db1 Source # | |
Migratory (IsoQ Definition) (IsoQ (Indexed PQ IO ())) Source # | pure rewindable migrations |
Defined in Squeal.PostgreSQL.Session.Migration | |
Migratory (IsoQ (Indexed PQ IO ())) (IsoQ (Indexed PQ IO ())) Source # | impure rewindable migrations |
Migratory (OpQ Definition) (OpQ (Indexed PQ IO ())) Source # | pure rewinds |
Defined in Squeal.PostgreSQL.Session.Migration | |
Migratory (OpQ (Indexed PQ IO ())) (OpQ (Indexed PQ IO ())) Source # | impure rewinds |
Migratory (Indexed PQ IO ()) (Indexed PQ IO ()) Source # | impure migrations |
type PrettyPrintHaystack (haystack :: SchemasType) Source # | |
Defined in Squeal.PostgreSQL.Type.Schema type PrettyPrintHaystack (haystack :: SchemasType) = 'PrettyPrintInfo ('Text "schema (SchemaType)") ('Text "database (SchemasType)") ('Text " " :<>: 'ShowType (Sort (MapFst haystack))) | |
type PrettyPrintHaystack (haystack :: SchemaType) Source # | |
Defined in Squeal.PostgreSQL.Type.Schema type PrettyPrintHaystack (haystack :: SchemaType) = 'PrettyPrintInfo ('Text "table, view, typedef, index, function, or procedure (SchemumType)") ('Text "schema (SchemaType)") (PrettyPrintPartitionedSchema (PartitionSchema haystack)) |
PostgreSQL provides several index types: B-tree, Hash, GiST, SP-GiST, GIN and BRIN. Each index type uses a different algorithm that is best suited to different types of queries.
Btree | B-trees can handle equality and range queries on data that can be sorted into some ordering. |
Hash | Hash indexes can only handle simple equality comparisons. |
Gist | GiST indexes are not a single kind of index, but rather an infrastructure within which many different indexing strategies can be implemented. |
Spgist | SP-GiST indexes, like GiST indexes, offer an infrastructure that supports various kinds of searches. |
Gin | GIN indexes are “inverted indexes” which are appropriate for data values that contain multiple component values, such as arrays. |
Brin | BRIN indexes (a shorthand for Block Range INdexes) store summaries about the values stored in consecutive physical block ranges of a table. |
type FunctionType = ([NullType], ReturnsType) Source #
Use :=>
to pair the parameter types with the return
type of a function.
>>>
:{
type family Fn :: FunctionType where Fn = '[ 'NotNull 'PGint4] :=> 'Returns ('NotNull 'PGint4) :}
data ReturnsType Source #
Return type of a function
Returns NullType | function |
ReturnsTable RowType | set returning function |
type SchemaType = [(Symbol, SchemumType)] Source #
A schema of a database consists of a list of aliased,
user-defined SchemumType
s.
>>>
:{
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"] "public" "users" '["id"] ] :=> '[ "id" ::: 'Def :=> 'NotNull 'PGint4 , "user_id" ::: 'NoDef :=> 'NotNull 'PGint4 , "email" ::: 'NoDef :=> 'Null 'PGtext ]) ] :}
type SchemasType = [(Symbol, SchemaType)] Source #
A database contains one or more named schemas, which in turn contain tables. The same object name can be used in different schemas without conflict; for example, both schema1 and myschema can contain tables named mytable. Unlike databases, schemas are not rigidly separated: a user can access objects in any of the schemas in the database they are connected to, if they have privileges to do so.
There are several reasons why one might want to use schemas:
- To allow many users to use one database without interfering with each other.
- To organize database objects into logical groups to make them more manageable.
- Third-party applications can be put into separate schemas so they do not collide with the names of other objects.
type family Public (schema :: SchemaType) :: SchemasType where ... Source #
A type family to use for a single schema database.
Database Subsets
type family SubDB (db0 :: SchemasType) (db1 :: SchemasType) :: Bool where ... Source #
SubDB
checks that one SchemasType
is a sublist of another,
with the same ordering.
>>>
:kind! SubDB '["a" ::: '["b" ::: 'View '[]]] '["a" ::: '["b" ::: 'View '[], "c" ::: 'Typedef 'PGint4]]
SubDB '["a" ::: '["b" ::: 'View '[]]] '["a" ::: '["b" ::: 'View '[], "c" ::: 'Typedef 'PGint4]] :: Bool = 'True
type family SubsetDB (db0 :: SchemasType) (db1 :: SchemasType) :: Bool where ... Source #
SubsetDB
checks that one SchemasType
is a subset of another,
regardless of ordering.
>>>
:kind! SubsetDB '["a" ::: '["d" ::: 'Typedef 'PGint2, "b" ::: 'View '[]]] '["a" ::: '["b" ::: 'View '[], "c" ::: 'Typedef 'PGint4, "d" ::: 'Typedef 'PGint2]]
SubsetDB '["a" ::: '["d" ::: 'Typedef 'PGint2, "b" ::: 'View '[]]] '["a" ::: '["b" ::: 'View '[], "c" ::: 'Typedef 'PGint4, "d" ::: 'Typedef 'PGint2]] :: Bool = 'True
type family ElemDB (sch :: (Symbol, SchemaType)) (db :: SchemasType) :: Bool where ... Source #
ElemDB
checks that a schema may be found as a subset of another in a database,
regardless of ordering.
Constraint
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
an Optionality
with a NullType
to produce a ColumnType
or a TableConstraints
and a ColumnsType
to produce a TableType
.
data Optionality Source #
Optionality
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.
Instances
data TableConstraint Source #
TableConstraint
encodes various forms of data constraints
of columns in a table.
TableConstraint
s 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
type PrettyPrintHaystack (haystack :: TableConstraints) Source # | |
Defined in Squeal.PostgreSQL.Type.Schema type PrettyPrintHaystack (haystack :: TableConstraints) = 'PrettyPrintInfo ('Text "constraint (TableConstraint)") ('Text "table (TableConstraints)") ('ShowType (Sort (MapFst haystack))) |
type TableConstraints = [(Symbol, TableConstraint)] Source #
A TableConstraints
is a row of TableConstraint
s.
>>>
:{
type family UsersConstraints :: TableConstraints where UsersConstraints = '[ "pk_users" ::: 'PrimaryKey '["id"] ] :}
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.
Enumerated Label
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,
label
s are used for enum terms. A label
is called with
type application like label
@"beef".
Instances
label ~ label1 => IsPGlabel label (PGlabel label1) Source # | |
Defined in Squeal.PostgreSQL.Type.Schema | |
IsPGlabel label (y -> K y label) Source # | |
Defined in Squeal.PostgreSQL.Type.Schema | |
IsPGlabel label (y -> NP (K y :: Symbol -> Type) '[label]) Source # | |
labels ~ '[label] => IsPGlabel label (NP PGlabel labels) Source # | |
IsPGlabel label0 (NS PGlabel (label0 ': labels)) Source # | |
IsPGlabel label0 (NS PGlabel labels) => IsPGlabel label0 (NS PGlabel (label1 ': labels)) Source # | |
(KnownSymbol label, In label labels) => IsPGlabel label (Expression grp lat with db params from (null ('PGenum labels))) Source # | |
Defined in Squeal.PostgreSQL.Expression label :: Expression grp lat with db params from (null ('PGenum labels)) Source # |
data PGlabel (label :: Symbol) Source #
Instances
label ~ label1 => IsPGlabel label (PGlabel label1) Source # | |
Defined in Squeal.PostgreSQL.Type.Schema | |
labels ~ '[label] => IsPGlabel label (NP PGlabel labels) Source # | |
IsPGlabel label0 (NS PGlabel (label0 ': labels)) Source # | |
IsPGlabel label0 (NS PGlabel labels) => IsPGlabel label0 (NS PGlabel (label1 ': labels)) Source # | |
KnownSymbol label => RenderSQL (PGlabel label) Source # | |
Defined in Squeal.PostgreSQL.Type.Schema renderSQL :: PGlabel label -> ByteString Source # | |
All KnownSymbol labels => RenderSQL (NP PGlabel labels) Source # | |
Defined in Squeal.PostgreSQL.Type.Schema |
Data Definition
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
.
type family CreateIfNotExists alias x xs where ... Source #
Similar to Create
but no error on pre-existence
CreateIfNotExists alias x '[] = '[alias ::: x] | |
CreateIfNotExists alias x ((alias ::: y) ': xs) = (alias ::: y) ': xs | |
CreateIfNotExists alias y (x ': xs) = x ': CreateIfNotExists alias y xs |
type family CreateOrReplace alias x xs where ... Source #
Similar to Create
but used to replace values
with the same type.
CreateOrReplace alias x '[] = '[alias ::: x] | |
CreateOrReplace alias x ((alias ::: x) ': xs) = (alias ::: x) ': xs | |
CreateOrReplace alias x ((alias ::: y) ': xs) = TypeError ((((('Text "CreateOrReplace: expected type " :<>: 'ShowType x) :<>: 'Text " but alias ") :<>: 'ShowType alias) :<>: 'Text " has type ") :<>: 'ShowType y) | |
CreateOrReplace alias y (x ': xs) = x ': CreateOrReplace 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.
type family DropSchemum alias sch xs where ... Source #
Drop a particular flavor of schemum type
DropSchemum alias sch '[] = TypeError (('Text "DropSchemum: alias " :<>: 'ShowType alias) :<>: 'Text " does not exist") | |
DropSchemum alias sch ((alias ::: sch x) ': xs) = xs | |
DropSchemum alias sch0 ((alias ::: sch1 x) ': xs) = TypeError ((((('Text "DropSchemum: expected schemum " :<>: 'ShowType sch0) :<>: 'Text " but alias ") :<>: 'ShowType alias) :<>: 'Text " has schemum ") :<>: 'ShowType sch1) | |
DropSchemum alias sch (x ': xs) = x ': DropSchemum alias sch xs |
type family DropIfExists alias xs where ... Source #
Similar to Drop
but no error on non-existence
DropIfExists alias '[] = '[] | |
DropIfExists alias ((alias ::: x) ': xs) = xs | |
DropIfExists alias (x ': xs) = x ': DropIfExists alias xs |
type family DropSchemumIfExists alias sch xs where ... Source #
Similar to DropSchemum
but no error on non-existence
DropSchemumIfExists alias sch '[] = '[] | |
DropSchemumIfExists alias sch ((alias ::: sch x) ': xs) = xs | |
DropSchemumIfExists alias sch0 ((alias ::: sch1 x) ': xs) = TypeError ((((('Text "DropSchemumIfExists: expected schemum " :<>: 'ShowType sch1) :<>: 'Text " but alias ") :<>: 'ShowType alias) :<>: 'Text " has schemum ") :<>: 'ShowType sch0) | |
DropSchemumIfExists alias sch (x ': xs) = x ': DropSchemumIfExists alias sch 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
.
type family AlterIfExists alias x xs where ... Source #
Similar to Alter
but no error on non-existence
AlterIfExists alias x '[] = '[] | |
AlterIfExists alias x1 ((alias ::: x0) ': xs) = (alias ::: x1) ': xs | |
AlterIfExists alias x1 (x0 ': xs) = x0 ': AlterIfExists 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
.
type family RenameIfExists alias0 alias1 xs where ... Source #
Similar to Rename
but no error on non-existence
RenameIfExists alias x '[] = '[] | |
RenameIfExists alias0 alias1 ((alias0 ::: x0) ': xs) = (alias1 ::: x0) ': xs | |
RenameIfExists alias0 alias1 (x ': xs) = x ': RenameIfExists alias0 alias1 xs |
type family SetSchema sch0 sch1 schema0 schema1 obj srt ty db where ... Source #
Move an object from one schema to another
SetSchema sch0 sch1 schema0 schema1 obj srt ty db = Alter sch1 (Create obj (srt ty) schema1) (Alter sch0 (DropSchemum obj srt schema0) db) |
type family ConstraintInvolves column constraint where ... Source #
Check if a TableConstraint
involves a column
ConstraintInvolves column ('Check columns) = column `Elem` columns | |
ConstraintInvolves column ('Unique columns) = column `Elem` columns | |
ConstraintInvolves column ('PrimaryKey columns) = column `Elem` columns | |
ConstraintInvolves column ('ForeignKey columns sch tab refcolumns) = column `Elem` columns |
type family DropIfConstraintsInvolve column constraints where ... Source #
Drop all TableConstraint
s that involve a column
DropIfConstraintsInvolve column '[] = '[] | |
DropIfConstraintsInvolve column ((alias ::: constraint) ': constraints) = If (ConstraintInvolves column constraint) (DropIfConstraintsInvolve column constraints) ((alias ::: constraint) ': DropIfConstraintsInvolve column constraints) |
Type Classification
type PGNum = '['PGint2, 'PGint4, 'PGint8, 'PGnumeric, 'PGfloat4, 'PGfloat8] Source #
Numeric Postgres types.
type PGJsonType = '['PGjson, 'PGjsonb] Source #
Is a type a valid JSON type?
class SamePGType (ty0 :: (Symbol, ColumnType)) (ty1 :: (Symbol, ColumnType)) Source #
Equality constraint on the underlying PGType
of two columns.
Instances
ty0 ~ ty1 => SamePGType (alias0 ::: (def0 :=> null0 ty0)) (alias1 ::: (def1 :=> null1 ty1)) Source # | |
Defined in Squeal.PostgreSQL.Type.Schema |
type family AllNotNull (columns :: ColumnsType) :: Constraint where ... Source #
AllNotNull
is a constraint that proves a ColumnsType
has no NULL
s.
AllNotNull ((_ ::: (_ :=> 'NotNull _)) ': columns) = AllNotNull columns | |
AllNotNull '[] = () |
type family NotAllNull (columns :: ColumnsType) :: Constraint where ... Source #
NotAllNull
is a constraint that proves a ColumnsType
has some
NOT NULL
.
NotAllNull ((_ ::: (_ :=> 'NotNull _)) ': _) = () | |
NotAllNull ((_ ::: (_ :=> 'Null _)) ': columns) = NotAllNull columns |
Nullification
type family NullifyType (ty :: NullType) :: NullType where ... Source #
NullifyType
is an idempotent that nullifies a NullType
.
NullifyType (null ty) = 'Null ty |
type family NullifyRow (columns :: RowType) :: RowType where ... Source #
NullifyRow
is an idempotent that nullifies a RowType
.
NullifyRow ((column ::: ty) ': columns) = (column ::: NullifyType ty) ': NullifyRow columns | |
NullifyRow '[] = '[] |
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
.
NullifyFrom ((table ::: columns) ': tables) = (table ::: NullifyRow columns) ': NullifyFrom tables | |
NullifyFrom '[] = '[] |
Table Conversion
type family TableToColumns (table :: TableType) :: ColumnsType where ... Source #
TableToColumns
removes table constraints.
TableToColumns (constraints :=> columns) = columns |
type family ColumnsToRow (columns :: ColumnsType) :: RowType where ... Source #
ColumnsToRow
removes column constraints.
ColumnsToRow ((column ::: (_ :=> ty)) ': columns) = (column ::: ty) ': ColumnsToRow columns | |
ColumnsToRow '[] = '[] |
type family TableToRow (table :: TableType) :: RowType where ... Source #
Convert a table to a row type.
TableToRow tab = ColumnsToRow (TableToColumns tab) |
Updatable
type Updatable table columns = (All (HasIn (TableToColumns table)) columns, AllUnique columns, SListI (TableToColumns table)) Source #
Updatable lists of columns
class AllUnique (xs :: [(Symbol, a)]) Source #
No elem of xs
appears more than once, in the context of assignment.
User Type Lookup
type family SchemaEnums schema where ... Source #
Filters a schema down to labels of all enum typedefs.
SchemaEnums '[] = '[] | |
SchemaEnums ((enum ::: 'Typedef ('PGenum labels)) ': schema) = (enum ::: labels) ': SchemaEnums schema | |
SchemaEnums (_ ': schema) = SchemaEnums schema |
type family DbRelations db where ... Source #
Filters schemas down to rows of relations; all composites, tables and views.
DbRelations '[] = '[] | |
DbRelations ((sch ::: schema) ': schemas) = (sch ::: SchemaRelations schema) ': DbRelations schemas |
type family SchemaRelations schema where ... Source #
Filters a schema down to rows of relations; all composites, tables and views.
SchemaRelations '[] = '[] | |
SchemaRelations ((ty ::: 'Typedef ('PGcomposite row)) ': schema) = (ty ::: row) ': SchemaRelations schema | |
SchemaRelations ((tab ::: 'Table table) ': schema) = (tab ::: TableToRow table) ': SchemaRelations schema | |
SchemaRelations ((vw ::: 'View row) ': schema) = (vw ::: row) ': SchemaRelations schema | |
SchemaRelations (_ ': schema) = SchemaRelations schema |
type family FindQualified err xss x where ... Source #
Find fully qualified name with a type error if lookup fails. This is used to find the qualified name of a user defined type.
>>>
:kind! FindQualified "my error message:"
FindQualified "my error message:" :: [(k1, [(k2, k3)])] -> k3 -> (k1, k2) = FindQualified "my error message:"
>>>
:kind! FindQualified "couldn't find type:" '[ "foo" ::: '["bar" ::: Double]] Double
FindQualified "couldn't find type:" '[ "foo" ::: '["bar" ::: Double]] Double :: (Symbol, Symbol) = '("foo", "bar")
>>>
:kind! FindQualified "couldn't find type:" '[ "foo" ::: '["bar" ::: Double]] Bool
FindQualified "couldn't find type:" '[ "foo" ::: '["bar" ::: Double]] Bool :: (Symbol, Symbol) = (TypeError ...)
FindQualified err '[] x = TypeError ('Text err :$$: 'ShowType x) | |
FindQualified err ('(nsp, xs) ': xss) x = FindNamespace err nsp (FindName xs x) xss x |
type family FindName xs x where ... Source #
Used in FindQualified
type family FindNamespace err nsp name xss x where ... Source #
Used in FindQualified
FindNamespace err _ 'Nothing xss x = FindQualified err xss x | |
FindNamespace _ nsp ('Just name) _ _ = '(nsp, name) |
Schema Error Printing
type family PrettyPrintPartitionedSchema (schema :: PartitionedSchema) :: ErrorMessage where ... Source #
PrettyPrintPartitionedSchema
makes a nice ErrorMessage
showing a PartitionedSchema
,
only including the names of the things in it and not the values. Additionally, empty
fields are omitted
PrettyPrintPartitionedSchema schema = IntersperseNewlines (FilterNonEmpty [FieldIfNonEmpty "Tables" (SchemaTables schema), FieldIfNonEmpty "Views" (SchemaViews schema), FieldIfNonEmpty "Types" (SchemaTypes schema), FieldIfNonEmpty "Indexes" (SchemaIndexes schema), FieldIfNonEmpty "Functions" (SchemaFunctions schema), FieldIfNonEmpty "Procedures" (SchemaProcedures schema), FieldIfNonEmpty "Unsafe schema items" (SchemaUnsafes schema)]) |
data PartitionedSchema Source #
A PartitionedSchema
is a SchemaType
where each constructor of SchemumType
has
been separated into its own list
type PartitionSchema schema = PartitionSchema' schema ('PartitionedSchema '[] '[] '[] '[] '[] '[] '[]) Source #
PartitionSchema
partitions a SchemaType
into a PartitionedSchema
type family SchemaFunctions (schema :: PartitionedSchema) :: [(Symbol, FunctionType)] where ... Source #
Get the functions from a PartitionedSchema
SchemaFunctions ('PartitionedSchema _ _ _ _ functions _ _) = functions |
type family SchemaIndexes (schema :: PartitionedSchema) :: [(Symbol, IndexType)] where ... Source #
Get the indexes from a PartitionedSchema
SchemaIndexes ('PartitionedSchema _ _ _ indexes _ _ _) = indexes |
type family SchemaProcedures (schema :: PartitionedSchema) :: [(Symbol, [NullType])] where ... Source #
Get the procedured from a PartitionedSchema
SchemaProcedures ('PartitionedSchema _ _ _ _ _ procedures _) = procedures |
type family SchemaTables (schema :: PartitionedSchema) :: [(Symbol, TableType)] where ... Source #
Get the tables from a PartitionedSchema
SchemaTables ('PartitionedSchema tables _ _ _ _ _ _) = tables |
type family SchemaTypes (schema :: PartitionedSchema) :: [(Symbol, PGType)] where ... Source #
Get the typedefs from a PartitionedSchema
SchemaTypes ('PartitionedSchema _ _ types _ _ _ _) = types |
type family SchemaUnsafes (schema :: PartitionedSchema) :: [(Symbol, Symbol)] where ... Source #
Get the unsafe schema types from a PartitionedSchema
SchemaUnsafes ('PartitionedSchema _ _ _ _ _ _ unsafes) = unsafes |
type family SchemaViews (schema :: PartitionedSchema) :: [(Symbol, RowType)] where ... Source #
Get the views from a PartitionedSchema
SchemaViews ('PartitionedSchema _ views _ _ _ _ _) = views |
type family IntersperseNewlines (ls :: [ErrorMessage]) :: ErrorMessage where ... Source #
Vertically concatenate error messages.
IntersperseNewlines (x ': (y ': '[])) = x :$$: y | |
IntersperseNewlines (x ': xs) = x :$$: IntersperseNewlines xs | |
IntersperseNewlines '[] = 'Text "" |
type family FilterNonEmpty (ls :: [ErrorMessage]) :: [ErrorMessage] where ... Source #
Filter out empty error messages.
FilterNonEmpty ('Text "" ': rest) = FilterNonEmpty rest | |
FilterNonEmpty (x ': rest) = x ': FilterNonEmpty rest | |
FilterNonEmpty '[] = '[] |
type family FieldIfNonEmpty (fieldName :: Symbol) (value :: [(Symbol, k)]) :: ErrorMessage where ... Source #
Print field name (if corresponding values are non-empty).
type family PartitionSchema' (remaining :: SchemaType) (acc :: PartitionedSchema) :: PartitionedSchema where ... Source #
Utility type family for PartitionSchema
.
PartitionSchema' '[] ps = ps | |
PartitionSchema' ('(s, 'Table table) ': rest) ('PartitionedSchema tables views types indexes functions procedures unsafe) = PartitionSchema' rest ('PartitionedSchema ('(s, table) ': tables) views types indexes functions procedures unsafe) | |
PartitionSchema' ('(s, 'View view) ': rest) ('PartitionedSchema tables views types indexes functions procedures unsafe) = PartitionSchema' rest ('PartitionedSchema tables ('(s, view) ': views) types indexes functions procedures unsafe) | |
PartitionSchema' ('(s, 'Typedef typ) ': rest) ('PartitionedSchema tables views types indexes functions procedures unsafe) = PartitionSchema' rest ('PartitionedSchema tables views ('(s, typ) ': types) indexes functions procedures unsafe) | |
PartitionSchema' ('(s, 'Index ix) ': rest) ('PartitionedSchema tables views types indexes functions procedures unsafe) = PartitionSchema' rest ('PartitionedSchema tables views types ('(s, ix) ': indexes) functions procedures unsafe) | |
PartitionSchema' ('(s, 'Function f) ': rest) ('PartitionedSchema tables views types indexes functions procedures unsafe) = PartitionSchema' rest ('PartitionedSchema tables views types indexes ('(s, f) ': functions) procedures unsafe) | |
PartitionSchema' ('(s, 'Procedure p) ': rest) ('PartitionedSchema tables views types indexes functions procedures unsafe) = PartitionSchema' rest ('PartitionedSchema tables views types indexes functions ('(s, p) ': procedures) unsafe) | |
PartitionSchema' ('(s, 'UnsafeSchemum u) ': rest) ('PartitionedSchema tables views types indexes functions procedures unsafe) = PartitionSchema' rest ('PartitionedSchema tables views types indexes functions procedures ('(s, u) ': unsafe)) |