| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Database.Beam.Postgres.Syntax
Description
Data types for Postgres syntax. Access is given mainly for extension modules. The types and definitions here are likely to change.
- data PgSyntaxF f where
- EmitByteString :: ByteString -> f -> PgSyntaxF f
 - EmitBuilder :: Builder -> f -> PgSyntaxF f
 - EscapeString :: ByteString -> f -> PgSyntaxF f
 - EscapeBytea :: ByteString -> f -> PgSyntaxF f
 - EscapeIdentifier :: ByteString -> f -> PgSyntaxF f
 
 - type PgSyntaxM = F PgSyntaxF
 - newtype PgSyntax = PgSyntax {
- buildPgSyntax :: PgSyntaxM ()
 
 - emit :: ByteString -> PgSyntax
 - emitBuilder :: Builder -> PgSyntax
 - escapeString :: ByteString -> PgSyntax
 - escapeBytea :: ByteString -> PgSyntax
 - escapeIdentifier :: ByteString -> PgSyntax
 - pgParens :: PgSyntax -> PgSyntax
 - nextSyntaxStep :: PgSyntaxF f -> f
 - data PgCommandSyntax = PgCommandSyntax {}
 - data PgCommandType
 - newtype PgSelectSyntax = PgSelectSyntax {}
 - newtype PgSelectSetQuantifierSyntax = PgSelectSetQuantifierSyntax {}
 - newtype PgInsertSyntax = PgInsertSyntax {}
 - newtype PgDeleteSyntax = PgDeleteSyntax {}
 - newtype PgUpdateSyntax = PgUpdateSyntax {}
 - newtype PgExpressionSyntax = PgExpressionSyntax {}
 - newtype PgFromSyntax = PgFromSyntax {}
 - newtype PgComparisonQuantifierSyntax = PgComparisonQuantifierSyntax {}
 - newtype PgExtractFieldSyntax = PgExtractFieldSyntax {}
 - newtype PgProjectionSyntax = PgProjectionSyntax {}
 - newtype PgGroupingSyntax = PgGroupingSyntax {}
 - data PgOrderingSyntax = PgOrderingSyntax {
- pgOrderingSyntax :: PgSyntax
 - pgOrderingNullOrdering :: Maybe PgNullOrdering
 
 - newtype PgValueSyntax = PgValueSyntax {}
 - newtype PgTableSourceSyntax = PgTableSourceSyntax {}
 - newtype PgFieldNameSyntax = PgFieldNameSyntax {}
 - newtype PgAggregationSetQuantifierSyntax = PgAggregationSetQuantifierSyntax {}
 - newtype PgInsertValuesSyntax = PgInsertValuesSyntax {}
 - newtype PgInsertOnConflictSyntax = PgInsertOnConflictSyntax {}
 - newtype PgInsertOnConflictTargetSyntax = PgInsertOnConflictTargetSyntax {}
 - newtype PgConflictActionSyntax = PgConflictActionSyntax {}
 - newtype PgCreateTableSyntax = PgCreateTableSyntax {}
 - data PgTableOptionsSyntax = PgTableOptionsSyntax PgSyntax PgSyntax
 - newtype PgColumnSchemaSyntax = PgColumnSchemaSyntax {}
 - data PgDataTypeSyntax = PgDataTypeSyntax {}
 - data PgColumnConstraintDefinitionSyntax = PgColumnConstraintDefinitionSyntax {}
 - data PgColumnConstraintSyntax = PgColumnConstraintSyntax {}
 - newtype PgTableConstraintSyntax = PgTableConstraintSyntax {}
 - data PgMatchTypeSyntax = PgMatchTypeSyntax {}
 - data PgReferentialActionSyntax = PgReferentialActionSyntax {}
 - newtype PgAlterTableSyntax = PgAlterTableSyntax {}
 - newtype PgAlterTableActionSyntax = PgAlterTableActionSyntax {}
 - newtype PgAlterColumnActionSyntax = PgAlterColumnActionSyntax {}
 - newtype PgWindowFrameSyntax = PgWindowFrameSyntax {}
 - newtype PgWindowFrameBoundsSyntax = PgWindowFrameBoundsSyntax {}
 - newtype PgWindowFrameBoundSyntax = PgWindowFrameBoundSyntax {}
 - data PgSelectLockingClauseSyntax = PgSelectLockingClauseSyntax {}
 - data PgSelectLockingStrength
 - data PgSelectLockingOptions
 - fromPgSelectLockingClause :: PgSelectLockingClauseSyntax -> PgSyntax
 - pgSelectStmt :: PgSelectTableSyntax -> [PgOrderingSyntax] -> Maybe Integer -> Maybe Integer -> Maybe PgSelectLockingClauseSyntax -> PgSelectSyntax
 - data PgDataTypeDescr
 - pgCreateExtensionSyntax :: Text -> PgCommandSyntax
 - pgDropExtensionSyntax :: Text -> PgCommandSyntax
 - insertDefaults :: SqlInsertValues PgInsertValuesSyntax tbl
 - pgSimpleMatchSyntax :: PgMatchTypeSyntax
 - pgSelectSetQuantifierDistinctOn :: [PgExpressionSyntax] -> PgSelectSetQuantifierSyntax
 - pgDataTypeJSON :: Value -> BeamSerializedDataType
 - pgTsQueryType :: PgDataTypeSyntax
 - pgTsVectorType :: PgDataTypeSyntax
 - pgJsonType :: PgDataTypeSyntax
 - pgJsonbType :: PgDataTypeSyntax
 - pgUuidType :: PgDataTypeSyntax
 - pgMoneyType :: PgDataTypeSyntax
 - pgTsQueryTypeInfo :: TypeInfo
 - pgTsVectorTypeInfo :: TypeInfo
 - pgByteaType :: PgDataTypeSyntax
 - pgTextType :: PgDataTypeSyntax
 - pgUnboundedArrayType :: PgDataTypeSyntax -> PgDataTypeSyntax
 - pgSerialType :: PgDataTypeSyntax
 - pgSmallSerialType :: PgDataTypeSyntax
 - pgBigSerialType :: PgDataTypeSyntax
 - pgQuotedIdentifier :: Text -> PgSyntax
 - pgSepBy :: PgSyntax -> [PgSyntax] -> PgSyntax
 - pgDebugRenderSyntax :: PgSyntax -> IO ()
 - pgRenderSyntaxScript :: PgSyntax -> ByteString
 - pgBuildAction :: [Action] -> PgSyntax
 - pgBinOp :: ByteString -> PgExpressionSyntax -> PgExpressionSyntax -> PgExpressionSyntax
 - pgCompOp :: ByteString -> Maybe PgComparisonQuantifierSyntax -> PgExpressionSyntax -> PgExpressionSyntax -> PgExpressionSyntax
 - pgUnOp :: ByteString -> PgExpressionSyntax -> PgExpressionSyntax
 - pgPostFix :: ByteString -> PgExpressionSyntax -> PgExpressionSyntax
 - pgTestSyntax :: PgSyntax -> [PgSyntaxPrim]
 - data PostgresInaccessible
 
Documentation
data PgSyntaxF f where Source #
Constructors
| EmitByteString :: ByteString -> f -> PgSyntaxF f | |
| EmitBuilder :: Builder -> f -> PgSyntaxF f | |
| EscapeString :: ByteString -> f -> PgSyntaxF f | |
| EscapeBytea :: ByteString -> f -> PgSyntaxF f | |
| EscapeIdentifier :: ByteString -> f -> PgSyntaxF f | 
A piece of Postgres SQL syntax, which may contain embedded escaped byte and
 text sequences. PgSyntax composes monoidally, and may be created with
 emit, emitBuilder, escapeString, escapBytea, and escapeIdentifier.
Constructors
| PgSyntax | |
Fields 
  | |
emit :: ByteString -> PgSyntax Source #
emitBuilder :: Builder -> PgSyntax Source #
escapeString :: ByteString -> PgSyntax Source #
escapeBytea :: ByteString -> PgSyntax Source #
nextSyntaxStep :: PgSyntaxF f -> f Source #
data PgCommandSyntax Source #
Representation of an arbitrary Postgres command. This is the combination of
 the command syntax (repesented by PgSyntax), as well as the type of command
 (represented by PgCommandType). The command type is necessary for us to
 know how to retrieve results from the database.
Constructors
| PgCommandSyntax | |
Fields  | |
Instances
data PgCommandType Source #
Constructors
| PgCommandTypeQuery | |
| PgCommandTypeDdl | |
| PgCommandTypeDataUpdate | |
| PgCommandTypeDataUpdateReturning | 
Instances
newtype PgSelectSetQuantifierSyntax Source #
Constructors
| PgSelectSetQuantifierSyntax | |
Fields  | |
newtype PgInsertSyntax Source #
IsSql92InsertSyntax for Postgres
Constructors
| PgInsertSyntax | |
Fields  | |
Instances
newtype PgDeleteSyntax Source #
IsSql92DeleteSyntax for Postgres
Constructors
| PgDeleteSyntax | |
Fields  | |
Instances
newtype PgExpressionSyntax Source #
Constructors
| PgExpressionSyntax | |
Fields  | |
Instances
newtype PgFromSyntax Source #
Constructors
| PgFromSyntax | |
Fields  | |
newtype PgComparisonQuantifierSyntax Source #
Constructors
| PgComparisonQuantifierSyntax | |
Fields  | |
newtype PgExtractFieldSyntax Source #
Constructors
| PgExtractFieldSyntax | |
Fields  | |
newtype PgProjectionSyntax Source #
Constructors
| PgProjectionSyntax | |
Fields  | |
newtype PgGroupingSyntax Source #
Constructors
| PgGroupingSyntax | |
Fields  | |
data PgOrderingSyntax Source #
Constructors
| PgOrderingSyntax | |
Fields 
  | |
newtype PgValueSyntax Source #
Constructors
| PgValueSyntax | |
Fields  | |
Instances
newtype PgTableSourceSyntax Source #
Constructors
| PgTableSourceSyntax | |
Fields  | |
newtype PgAggregationSetQuantifierSyntax Source #
Constructors
| PgAggregationSetQuantifierSyntax | |
Fields  | |
newtype PgInsertValuesSyntax Source #
Constructors
| PgInsertValuesSyntax | |
Fields  | |
newtype PgInsertOnConflictSyntax Source #
Constructors
| PgInsertOnConflictSyntax | |
Fields  | |
newtype PgInsertOnConflictTargetSyntax Source #
Constructors
| PgInsertOnConflictTargetSyntax | |
Fields  | |
newtype PgConflictActionSyntax Source #
Constructors
| PgConflictActionSyntax | |
Fields  | |
newtype PgCreateTableSyntax Source #
Constructors
| PgCreateTableSyntax | |
Fields  | |
data PgTableOptionsSyntax Source #
Constructors
| PgTableOptionsSyntax PgSyntax PgSyntax | 
newtype PgColumnSchemaSyntax Source #
Constructors
| PgColumnSchemaSyntax | |
Fields  | |
Instances
data PgDataTypeSyntax Source #
Constructors
| PgDataTypeSyntax | |
Instances
data PgColumnConstraintDefinitionSyntax Source #
Constructors
| PgColumnConstraintDefinitionSyntax | |
Instances
data PgColumnConstraintSyntax Source #
Constructors
| PgColumnConstraintSyntax | |
Instances
newtype PgTableConstraintSyntax Source #
Constructors
| PgTableConstraintSyntax | |
Fields  | |
data PgReferentialActionSyntax Source #
Constructors
| PgReferentialActionSyntax | |
newtype PgAlterTableSyntax Source #
Constructors
| PgAlterTableSyntax | |
Fields  | |
newtype PgAlterTableActionSyntax Source #
Constructors
| PgAlterTableActionSyntax | |
Fields  | |
newtype PgAlterColumnActionSyntax Source #
Constructors
| PgAlterColumnActionSyntax | |
Fields  | |
newtype PgWindowFrameSyntax Source #
Constructors
| PgWindowFrameSyntax | |
Fields  | |
newtype PgWindowFrameBoundsSyntax Source #
Constructors
| PgWindowFrameBoundsSyntax | |
Fields  | |
newtype PgWindowFrameBoundSyntax Source #
Constructors
| PgWindowFrameBoundSyntax | |
Fields  | |
data PgSelectLockingStrength Source #
Specifies the level of lock that will be taken against a row. See the manual section for more information.
Constructors
| PgSelectLockingStrengthUpdate | UPDATE  | 
| PgSelectLockingStrengthNoKeyUpdate | NO KEY UPDATE  | 
| PgSelectLockingStrengthShare | SHARE  | 
| PgSelectLockingStrengthKeyShare | KEY SHARE  | 
data PgSelectLockingOptions Source #
Specifies how we should handle lock conflicts.
See the manual section for more information
Constructors
| PgSelectLockingOptionsNoWait | 
  | 
| PgSelectLockingOptionsSkipLocked | 
  | 
Arguments
| :: PgSelectTableSyntax | |
| -> [PgOrderingSyntax] | |
| -> Maybe Integer | LIMIT  | 
| -> Maybe Integer | OFFSET  | 
| -> Maybe PgSelectLockingClauseSyntax | |
| -> PgSelectSyntax | 
data PgDataTypeDescr Source #
Constructors
| PgDataTypeDescrOid Oid (Maybe Int32) | |
| PgDataTypeDescrDomain Text | 
Instances
pgTsVectorTypeInfo :: TypeInfo Source #
Postgres TypeInfo for tsvector TODO Is the Oid stable from postgres instance to postgres instance?
pgQuotedIdentifier :: Text -> PgSyntax Source #
pgDebugRenderSyntax :: PgSyntax -> IO () Source #
pgBuildAction :: [Action] -> PgSyntax Source #
pgCompOp :: ByteString -> Maybe PgComparisonQuantifierSyntax -> PgExpressionSyntax -> PgExpressionSyntax -> PgExpressionSyntax Source #
pgTestSyntax :: PgSyntax -> [PgSyntaxPrim] Source #
data PostgresInaccessible Source #