| Copyright | Flipstone Technology Partners 2023 |
|---|---|
| License | MIT |
| Stability | Stable |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Orville.PostgreSQL.PgCatalog
Description
Since: 1.0.0.0
Synopsis
- data PgSequence = PgSequence {}
- pgSequenceTable :: TableDefinition (HasKey Oid) PgSequence PgSequence
- sequencePgClassOidField :: FieldDefinition NotNull Oid
- data PgNamespace = PgNamespace {}
- data NamespaceName
- namespaceNameToString :: NamespaceName -> String
- pgNamespaceTable :: TableDefinition (HasKey Oid) PgNamespace PgNamespace
- namespaceNameField :: FieldDefinition NotNull NamespaceName
- data PgIndex = PgIndex {}
- pgIndexTable :: TableDefinition NoKey PgIndex PgIndex
- indexRelationOidField :: FieldDefinition NotNull Oid
- indexIsLiveField :: FieldDefinition NotNull Bool
- data PgConstraint = PgConstraint {
- pgConstraintOid :: Oid
- pgConstraintName :: ConstraintName
- pgConstraintNamespaceOid :: Oid
- pgConstraintType :: ConstraintType
- pgConstraintRelationOid :: Oid
- pgConstraintIndexOid :: Oid
- pgConstraintKey :: Maybe [AttributeNumber]
- pgConstraintForeignRelationOid :: Oid
- pgConstraintForeignKey :: Maybe [AttributeNumber]
- pgConstraintForeignKeyOnUpdateType :: Maybe ForeignKeyAction
- pgConstraintForeignKeyOnDeleteType :: Maybe ForeignKeyAction
- data ConstraintType
- data ConstraintName
- constraintNameToString :: ConstraintName -> String
- pgConstraintTable :: TableDefinition (HasKey Oid) PgConstraint PgConstraint
- constraintRelationOidField :: FieldDefinition NotNull Oid
- data PgClass = PgClass {}
- data RelationName
- relationNameToString :: RelationName -> String
- data RelationKind
- pgClassTable :: TableDefinition (HasKey Oid) PgClass PgClass
- relationNameField :: FieldDefinition NotNull RelationName
- namespaceOidField :: FieldDefinition NotNull Oid
- relationKindField :: FieldDefinition NotNull RelationKind
- data PgAttributeDefault = PgAttributeDefault {}
- pgAttributeDefaultTable :: TableDefinition NoKey PgAttributeDefault PgAttributeDefault
- attributeDefaultRelationOidField :: FieldDefinition NotNull Oid
- data PgAttribute = PgAttribute {}
- pgAttributeMaxLength :: PgAttribute -> Maybe Int32
- data AttributeName
- attributeNameToString :: AttributeName -> String
- data AttributeNumber
- attributeNumberToInt16 :: AttributeNumber -> Int16
- attributeNumberFromInt16 :: Int16 -> AttributeNumber
- attributeNumberTextBuilder :: AttributeNumber -> Builder
- attributeNumberParser :: Parser AttributeNumber
- isOrdinaryColumn :: PgAttribute -> Bool
- pgAttributeTable :: TableDefinition NoKey PgAttribute PgAttribute
- attributeRelationOidField :: FieldDefinition NotNull Oid
- attributeNameField :: FieldDefinition NotNull AttributeName
- attributeTypeOidField :: FieldDefinition NotNull Oid
- attributeLengthField :: FieldDefinition NotNull Int16
- attributeIsDroppedField :: FieldDefinition NotNull Bool
- attributeNumberTypeField :: String -> FieldDefinition NotNull AttributeNumber
- oidField :: FieldDefinition NotNull Oid
- oidTypeField :: String -> FieldDefinition NotNull Oid
- data DatabaseDescription = DatabaseDescription {}
- data RelationDescription = RelationDescription {}
- data ConstraintDescription = ConstraintDescription {}
- data ForeignRelationDescription = ForeignRelationDescription {}
- data IndexDescription = IndexDescription {}
- data IndexMember
- lookupRelation :: (NamespaceName, RelationName) -> DatabaseDescription -> Maybe RelationDescription
- lookupRelationOfKind :: RelationKind -> (NamespaceName, RelationName) -> DatabaseDescription -> Maybe RelationDescription
- lookupAttribute :: AttributeName -> RelationDescription -> Maybe PgAttribute
- lookupAttributeDefault :: PgAttribute -> RelationDescription -> Maybe PgAttributeDefault
- describeDatabaseRelations :: MonadOrville m => [(NamespaceName, RelationName)] -> m DatabaseDescription
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
| |
data NamespaceName Source #
A Haskell type for the name of a namespace.
Since: 1.0.0.0
Instances
| IsString NamespaceName Source # | |
Defined in Orville.PostgreSQL.PgCatalog.PgNamespace Methods fromString :: String -> NamespaceName # | |
| Show NamespaceName Source # | |
Defined in Orville.PostgreSQL.PgCatalog.PgNamespace Methods showsPrec :: Int -> NamespaceName -> ShowS # show :: NamespaceName -> String # showList :: [NamespaceName] -> ShowS # | |
| Eq NamespaceName Source # | |
Defined in Orville.PostgreSQL.PgCatalog.PgNamespace Methods (==) :: NamespaceName -> NamespaceName -> Bool # (/=) :: NamespaceName -> NamespaceName -> Bool # | |
| Ord NamespaceName Source # | |
Defined in Orville.PostgreSQL.PgCatalog.PgNamespace Methods compare :: NamespaceName -> NamespaceName -> Ordering # (<) :: NamespaceName -> NamespaceName -> Bool # (<=) :: NamespaceName -> NamespaceName -> Bool # (>) :: NamespaceName -> NamespaceName -> Bool # (>=) :: NamespaceName -> NamespaceName -> Bool # max :: NamespaceName -> NamespaceName -> NamespaceName # min :: NamespaceName -> NamespaceName -> NamespaceName # | |
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
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
| |
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
| |
data ConstraintType Source #
The type of constraint that a PgConstraint represents, as described at
https://www.postgresql.org/docs/13/catalog-pg-constraint.html.
Since: 1.0.0.0
Constructors
| CheckConstraint | |
| ForeignKeyConstraint | |
| PrimaryKeyConstraint | |
| UniqueConstraint | |
| ConstraintTrigger | |
| ExclusionConstraint |
Instances
| Show ConstraintType Source # | |
Defined in Orville.PostgreSQL.PgCatalog.PgConstraint Methods showsPrec :: Int -> ConstraintType -> ShowS # show :: ConstraintType -> String # showList :: [ConstraintType] -> ShowS # | |
| Eq ConstraintType Source # | |
Defined in Orville.PostgreSQL.PgCatalog.PgConstraint Methods (==) :: ConstraintType -> ConstraintType -> Bool # (/=) :: ConstraintType -> ConstraintType -> Bool # | |
data ConstraintName Source #
A Haskell type for the name of the constraint represented by a
PgConstraint.
Since: 1.0.0.0
Instances
| IsString ConstraintName Source # | |
Defined in Orville.PostgreSQL.PgCatalog.PgConstraint Methods fromString :: String -> ConstraintName # | |
| Show ConstraintName Source # | |
Defined in Orville.PostgreSQL.PgCatalog.PgConstraint Methods showsPrec :: Int -> ConstraintName -> ShowS # show :: ConstraintName -> String # showList :: [ConstraintName] -> ShowS # | |
| Eq ConstraintName Source # | |
Defined in Orville.PostgreSQL.PgCatalog.PgConstraint Methods (==) :: ConstraintName -> ConstraintName -> Bool # (/=) :: ConstraintName -> ConstraintName -> Bool # | |
| Ord ConstraintName Source # | |
Defined in Orville.PostgreSQL.PgCatalog.PgConstraint Methods compare :: ConstraintName -> ConstraintName -> Ordering # (<) :: ConstraintName -> ConstraintName -> Bool # (<=) :: ConstraintName -> ConstraintName -> Bool # (>) :: ConstraintName -> ConstraintName -> Bool # (>=) :: ConstraintName -> ConstraintName -> Bool # max :: ConstraintName -> ConstraintName -> ConstraintName # min :: ConstraintName -> ConstraintName -> ConstraintName # | |
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
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
| |
data RelationName Source #
A Haskell type for the name of the relation represented by a PgClass.
Since: 1.0.0.0
Instances
| IsString RelationName Source # | |
Defined in Orville.PostgreSQL.PgCatalog.PgClass Methods fromString :: String -> RelationName # | |
| Show RelationName Source # | |
Defined in Orville.PostgreSQL.PgCatalog.PgClass Methods showsPrec :: Int -> RelationName -> ShowS # show :: RelationName -> String # showList :: [RelationName] -> ShowS # | |
| Eq RelationName Source # | |
Defined in Orville.PostgreSQL.PgCatalog.PgClass | |
| Ord RelationName Source # | |
Defined in Orville.PostgreSQL.PgCatalog.PgClass Methods compare :: RelationName -> RelationName -> Ordering # (<) :: RelationName -> RelationName -> Bool # (<=) :: RelationName -> RelationName -> Bool # (>) :: RelationName -> RelationName -> Bool # (>=) :: RelationName -> RelationName -> Bool # max :: RelationName -> RelationName -> RelationName # min :: RelationName -> RelationName -> RelationName # | |
relationNameToString :: RelationName -> String Source #
Convert a RelationName to a plain String.
Since: 1.0.0.0
data RelationKind Source #
The kind of relation represented by a PgClass, as described at
https://www.postgresql.org/docs/13/catalog-pg-class.html.
Since: 1.0.0.0
Constructors
| OrdinaryTable | |
| Index | |
| Sequence | |
| ToastTable | |
| View | |
| MaterializedView | |
| CompositeType | |
| ForeignTable | |
| PartitionedTable | |
| PartitionedIndex |
Instances
| Show RelationKind Source # | |
Defined in Orville.PostgreSQL.PgCatalog.PgClass Methods showsPrec :: Int -> RelationKind -> ShowS # show :: RelationKind -> String # showList :: [RelationKind] -> ShowS # | |
| Eq RelationKind Source # | |
Defined in Orville.PostgreSQL.PgCatalog.PgClass | |
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
data AttributeName Source #
A Haskell type for the name of the attribute represented by a PgAttribute.
Since: 1.0.0.0
Instances
| IsString AttributeName Source # | |
Defined in Orville.PostgreSQL.PgCatalog.PgAttribute Methods fromString :: String -> AttributeName # | |
| Show AttributeName Source # | |
Defined in Orville.PostgreSQL.PgCatalog.PgAttribute Methods showsPrec :: Int -> AttributeName -> ShowS # show :: AttributeName -> String # showList :: [AttributeName] -> ShowS # | |
| Eq AttributeName Source # | |
Defined in Orville.PostgreSQL.PgCatalog.PgAttribute Methods (==) :: AttributeName -> AttributeName -> Bool # (/=) :: AttributeName -> AttributeName -> Bool # | |
| Ord AttributeName Source # | |
Defined in Orville.PostgreSQL.PgCatalog.PgAttribute Methods compare :: AttributeName -> AttributeName -> Ordering # (<) :: AttributeName -> AttributeName -> Bool # (<=) :: AttributeName -> AttributeName -> Bool # (>) :: AttributeName -> AttributeName -> Bool # (>=) :: AttributeName -> AttributeName -> Bool # max :: AttributeName -> AttributeName -> AttributeName # min :: AttributeName -> AttributeName -> AttributeName # | |
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
attributeNumberToInt16 :: AttributeNumber -> Int16 Source #
Converts an AttributeNumber to an integer.
attributeNumberFromInt16 :: Int16 -> AttributeNumber Source #
Converts an integer to an AttributeNumber.
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
attributeNumberTypeField :: String -> FieldDefinition NotNull AttributeNumber Source #
Builds a FieldDefinition for a field with type AttributeNumber.
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
Constructors
| DatabaseDescription | |
Fields | |
data RelationDescription Source #
A description of a particular relation in the PostgreSQL database, including the attributes of the relation.
Since: 1.0.0.0
Constructors
| RelationDescription | |
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
Constructors
| ConstraintDescription | |
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
Constructors
| ForeignRelationDescription | |
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
Constructors
| IndexDescription | |
Fields
| |
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
Constructors
| IndexAttribute PgAttribute | |
| IndexExpression |
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
lookupAttributeDefault :: PgAttribute -> RelationDescription -> Maybe PgAttributeDefault Source #
Find an attribute default 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