orville-postgresql-1.0.0.0: A Haskell library for PostgreSQL
CopyrightFlipstone Technology Partners 2023
LicenseMIT
StabilityStable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Orville.PostgreSQL.PgCatalog

Description

Since: 1.0.0.0

Synopsis

Documentation

data PgSequence Source #

The Haskell representation of data read from the pg_catalog.pg_sequence table. Rows in this table are sequences in PostgreSQL.

Since: 1.0.0.0

Constructors

PgSequence 

Fields

pgSequenceTable :: TableDefinition (HasKey Oid) PgSequence PgSequence Source #

An Orville TableDefinition for querying the pg_catalog.pg_sequence table.

Since: 1.0.0.0

sequencePgClassOidField :: FieldDefinition NotNull Oid Source #

The seqrelid column of the pg_cataglog.pg_sequence table.

Since: 1.0.0.0

data PgNamespace Source #

The Haskell representation of data read from the pg_catalog.pg_namespace table. Namespaces in pg_catalog correspond to "schema" concept in database organization.

Since: 1.0.0.0

Constructors

PgNamespace 

Fields

namespaceNameToString :: NamespaceName -> String Source #

Convert a NamespaceName to a plain String.

Since: 1.0.0.0

pgNamespaceTable :: TableDefinition (HasKey Oid) PgNamespace PgNamespace Source #

An Orville TableDefinition for querying the pg_catalog.pg_namespace table.

Since: 1.0.0.0

namespaceNameField :: FieldDefinition NotNull NamespaceName Source #

The nspname column of the pg_catalog.pg_namespace table.

Since: 1.0.0.0

data PgIndex Source #

The Haskell representation of data read from the pg_catalog.pg_index table. Rows in this table contain extended information about indices. Information about indices is also contained in the pg_catalog.pg_class table as well.

Since: 1.0.0.0

Constructors

PgIndex 

Fields

  • pgIndexPgClassOid :: Oid

    The PostgreSQL oid of the pg_class entry for this index.

  • pgIndexRelationOid :: Oid

    The PostgreSQL oid of the pg_class entry for the table that this index is for.

  • pgIndexAttributeNumbers :: [AttributeNumber]

    An array of attribute number references for the columns of the table that are included in the index. An attribute number of 0 indicates an expression over the table's columns rather than just a reference to a column.

    In PostgreSQL 11+ this includes both key columns and non-key-included columns. Orville is currently not aware of this distinction, however.

  • pgIndexIsUnique :: Bool

    Indicates whether this is a unique index.

  • pgIndexIsPrimary :: Bool

    Indicates whether this is the primary key index for the table.

  • pgIndexIsLive :: Bool

    When False, indicates that this index is in the process of being dropped and should be ignored.

pgIndexTable :: TableDefinition NoKey PgIndex PgIndex Source #

An Orville TableDefinition for querying the pg_catalog.pg_index table.

Since: 1.0.0.0

indexRelationOidField :: FieldDefinition NotNull Oid Source #

The indrelid column of the pg_index table.

Since: 1.0.0.0

indexIsLiveField :: FieldDefinition NotNull Bool Source #

The indislive column of the pg_index table.

Since: 1.0.0.0

data PgConstraint Source #

The Haskell representation of data read from the pg_catalog.pg_constraint table. Rows in this table correspond to check, primary key, unique, foreign key and exclusion constraints on tables.

Since: 1.0.0.0

Constructors

PgConstraint 

Fields

constraintNameToString :: ConstraintName -> String Source #

Converts a ConstraintName to a plain String.

Since: 1.0.0.0

pgConstraintTable :: TableDefinition (HasKey Oid) PgConstraint PgConstraint Source #

An Orville TableDefinition for querying the pg_catalog.pg_constraint table.

Since: 1.0.0.0

constraintRelationOidField :: FieldDefinition NotNull Oid Source #

The conrelid column of the pg_constraint table.

Since: 1.0.0.0

data PgClass Source #

The Haskell representation of data read from the pg_catalog.pg_class table. Rows in this table correspond to tables, indexes, sequences, views, materialized views, composite types and TOAST tables.

Since: 1.0.0.0

Constructors

PgClass 

Fields

relationNameToString :: RelationName -> String Source #

Convert a RelationName to a plain String.

Since: 1.0.0.0

pgClassTable :: TableDefinition (HasKey Oid) PgClass PgClass Source #

An Orville TableDefinition for querying the pg_catalog.pg_class table.

Since: 1.0.0.0

relationNameField :: FieldDefinition NotNull RelationName Source #

The relname column of the pg_catalog.pg_class table.

Since: 1.0.0.0

namespaceOidField :: FieldDefinition NotNull Oid Source #

The relnamespace column of the pg_catalog.pg_class table.

Since: 1.0.0.0

relationKindField :: FieldDefinition NotNull RelationKind Source #

The relkind column of the pg_catalog.pg_class table.

Since: 1.0.0.0

data PgAttributeDefault Source #

The Haskell representation of data read from the pg_catalog.pg_attrdef table.

Since: 1.0.0.0

Constructors

PgAttributeDefault 

Fields

pgAttributeDefaultTable :: TableDefinition NoKey PgAttributeDefault PgAttributeDefault Source #

An Orville TableDefinition for querying the pg_catalog.pg_attrdef table.

Since: 1.0.0.0

attributeDefaultRelationOidField :: FieldDefinition NotNull Oid Source #

The adrelid column of the pg_catalog.pg_attrdef table.

Since: 1.0.0.0

data PgAttribute Source #

The Haskell representation of data read from the pg_catalog.pg_attribute table. Rows in this table correspond to table columns, but also to attributes of other items from the pg_class table.

See also PgClass.

Since: 1.0.0.0

Constructors

PgAttribute 

Fields

pgAttributeMaxLength :: PgAttribute -> Maybe Int32 Source #

Returns the maximum length for an attribute with a variable length type, or Nothing if the length of the type is not variable.

Since: 1.0.0.0

attributeNameToString :: AttributeName -> String Source #

Converts an AttributeName to a plain String.

Since: 1.0.0.0

data AttributeNumber Source #

A Haskell type for the number of the attribute represented by a PgAttribute.

Since: 1.0.0.0

Instances

Instances details
Enum AttributeNumber Source # 
Instance details

Defined in Orville.PostgreSQL.PgCatalog.PgAttribute

Num AttributeNumber Source # 
Instance details

Defined in Orville.PostgreSQL.PgCatalog.PgAttribute

Integral AttributeNumber Source # 
Instance details

Defined in Orville.PostgreSQL.PgCatalog.PgAttribute

Real AttributeNumber Source # 
Instance details

Defined in Orville.PostgreSQL.PgCatalog.PgAttribute

Show AttributeNumber Source # 
Instance details

Defined in Orville.PostgreSQL.PgCatalog.PgAttribute

Eq AttributeNumber Source # 
Instance details

Defined in Orville.PostgreSQL.PgCatalog.PgAttribute

Ord AttributeNumber Source # 
Instance details

Defined in Orville.PostgreSQL.PgCatalog.PgAttribute

attributeNumberTextBuilder :: AttributeNumber -> Builder Source #

Encodes an AttributeNumber to lazy text as a builder.

Since: 1.0.0.0

attributeNumberParser :: Parser AttributeNumber Source #

Attoparsec parser for AttributeNumber.

Since: 1.0.0.0

isOrdinaryColumn :: PgAttribute -> Bool Source #

Determines whether the attribute represents a system column by inspecting the attribute's AttributeNumber. Ordinary columns have attribute numbers starting at 1.

Since: 1.0.0.0

pgAttributeTable :: TableDefinition NoKey PgAttribute PgAttribute Source #

An Orville TableDefinition for querying the pg_catalog.pg_attribute table.

Since: 1.0.0.0

attributeRelationOidField :: FieldDefinition NotNull Oid Source #

The attrelid column of the pg_catalog.pg_attribute table.

Since: 1.0.0.0

attributeNameField :: FieldDefinition NotNull AttributeName Source #

The attname column of the pg_catalog.pg_attribute table.

Since: 1.0.0.0

attributeTypeOidField :: FieldDefinition NotNull Oid Source #

The atttypid column of the pg_catalog.pg_attribute table.

Since: 1.0.0.0

attributeLengthField :: FieldDefinition NotNull Int16 Source #

The attlen column of the pg_catalog.pg_attribute table.

Since: 1.0.0.0

attributeIsDroppedField :: FieldDefinition NotNull Bool Source #

The attisdropped column of the pg_catalog.pg_attribute table.

Since: 1.0.0.0

oidField :: FieldDefinition NotNull Oid Source #

The oid field found on many (but not all!) pg_catalog tables.

Since: 1.0.0.0

oidTypeField :: String -> FieldDefinition NotNull Oid Source #

Builds a FieldDefinition with the given column name that stores an oid value.

Since: 1.0.0.0

data DatabaseDescription Source #

A description of selected items from a single PostgreSQL database. describeDatabaseRelations can be used to load the descriptions of request items.

Since: 1.0.0.0

data RelationDescription Source #

A description of a particular relation in the PostgreSQL database, including the attributes of the relation.

Since: 1.0.0.0

data ConstraintDescription Source #

A description of a particular constraint in the PostgreSQL database, including the attributes and relations that it references.

Since: 1.0.0.0

data ForeignRelationDescription Source #

A description of a relation in the PostgreSQL database that is referenced by a foreign key constraint, including the namespace that the relation belongs to.

Since: 1.0.0.0

data IndexDescription Source #

A description of an index in the PostgreSQL database, including the names of the attributes included in the index and the PgClass record of the index itself (NOT the PgClass of the table that the index is for).

Since: 1.0.0.0

data IndexMember Source #

A description of an index member in the PostgreSQL database. If the member is a simple attribute, the PgAttribute for that is provided. If it is an index over an expression, no further description is currently provided.

Since: 1.0.0.0

lookupRelation :: (NamespaceName, RelationName) -> DatabaseDescription -> Maybe RelationDescription Source #

Lookup a relation by its qualified name in the pg_catalog schema.

Since: 1.0.0.0

lookupRelationOfKind :: RelationKind -> (NamespaceName, RelationName) -> DatabaseDescription -> Maybe RelationDescription Source #

Lookup a relation by its qualified name in the pg_catalog schema. If the relation is not of the expected kind, Nothing is returned.

Since: 1.0.0.0

lookupAttribute :: AttributeName -> RelationDescription -> Maybe PgAttribute Source #

Find an attribute by name from the RelationDescription.

Since: 1.0.0.0

describeDatabaseRelations :: MonadOrville m => [(NamespaceName, RelationName)] -> m DatabaseDescription Source #

Describes the requested relations in the current database. If any of the relations do not exist, they will not have an entry in the returned description.

Each RelationDescription will contain all the attributes that currently exist for that relation, according to the pg_catalog tables.

Since: 1.0.0.0