Safe Haskell | Safe-Inferred |
---|---|
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.
Synopsis
- 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 PgTableNameSyntax = PgTableNameSyntax {}
- 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
- defaultPgValueSyntax :: ToField a => a -> PgValueSyntax
- data PgDataTypeDescr
- data PgHasEnum = PgHasEnum Text [Text]
- pgCreateExtensionSyntax :: Text -> PgCommandSyntax
- pgDropExtensionSyntax :: Text -> PgCommandSyntax
- pgCreateEnumSyntax :: Text -> [PgValueSyntax] -> PgCommandSyntax
- pgDropTypeSyntax :: Text -> PgCommandSyntax
- 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
- pgPointType :: PgDataTypeSyntax
- pgLineType :: PgDataTypeSyntax
- pgLineSegmentType :: PgDataTypeSyntax
- pgBoxType :: 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
IsSql92Syntax PgCommandSyntax Source # | |
Defined in Database.Beam.Postgres.Syntax Associated Types type Sql92SelectSyntax PgCommandSyntax # type Sql92InsertSyntax PgCommandSyntax # | |
IsSql92DdlCommandSyntax PgCommandSyntax Source # | |
Defined in Database.Beam.Postgres.Syntax Associated Types type Sql92DdlCommandCreateTableSyntax PgCommandSyntax # | |
type Sql92DeleteSyntax PgCommandSyntax Source # | |
Defined in Database.Beam.Postgres.Syntax | |
type Sql92InsertSyntax PgCommandSyntax Source # | |
Defined in Database.Beam.Postgres.Syntax | |
type Sql92SelectSyntax PgCommandSyntax Source # | |
Defined in Database.Beam.Postgres.Syntax | |
type Sql92UpdateSyntax PgCommandSyntax Source # | |
Defined in Database.Beam.Postgres.Syntax | |
type Sql92DdlCommandAlterTableSyntax PgCommandSyntax Source # | |
type Sql92DdlCommandCreateTableSyntax PgCommandSyntax Source # | |
type Sql92DdlCommandDropTableSyntax PgCommandSyntax Source # | |
data PgCommandType Source #
Constructors
PgCommandTypeQuery | |
PgCommandTypeDdl | |
PgCommandTypeDataUpdate | |
PgCommandTypeDataUpdateReturning |
Instances
Show PgCommandType Source # | |
Defined in Database.Beam.Postgres.Syntax Methods showsPrec :: Int -> PgCommandType -> ShowS # show :: PgCommandType -> String # showList :: [PgCommandType] -> ShowS # |
newtype PgSelectSyntax Source #
IsSql92SelectSyntax
for Postgres
Constructors
PgSelectSyntax | |
Fields |
Instances
IsSql92SelectSyntax PgSelectSyntax Source # | |
Defined in Database.Beam.Postgres.Syntax Associated Types Methods selectStmt :: Sql92SelectSelectTableSyntax PgSelectSyntax -> [Sql92SelectOrderingSyntax PgSelectSyntax] -> Maybe Integer -> Maybe Integer -> PgSelectSyntax # | |
IsSql99CommonTableExpressionSelectSyntax PgSelectSyntax Source # | |
Defined in Database.Beam.Postgres.Syntax Associated Types Methods withSyntax :: [Sql99SelectCTESyntax PgSelectSyntax] -> PgSelectSyntax -> PgSelectSyntax # | |
IsSql99RecursiveCommonTableExpressionSelectSyntax PgSelectSyntax Source # | |
Defined in Database.Beam.Postgres.Syntax Methods withRecursiveSyntax :: [Sql99SelectCTESyntax PgSelectSyntax] -> PgSelectSyntax -> PgSelectSyntax # | |
type Sql92SelectOrderingSyntax PgSelectSyntax Source # | |
Defined in Database.Beam.Postgres.Syntax | |
type Sql92SelectSelectTableSyntax PgSelectSyntax Source # | |
Defined in Database.Beam.Postgres.Syntax | |
type Sql99SelectCTESyntax PgSelectSyntax Source # | |
Defined in Database.Beam.Postgres.Syntax |
newtype PgSelectSetQuantifierSyntax Source #
Constructors
PgSelectSetQuantifierSyntax | |
Fields |
newtype PgInsertSyntax Source #
IsSql92InsertSyntax
for Postgres
Constructors
PgInsertSyntax | |
Fields |
Instances
IsSql92InsertSyntax PgInsertSyntax Source # | |
Defined in Database.Beam.Postgres.Syntax Associated Types Methods insertStmt :: Sql92InsertTableNameSyntax PgInsertSyntax -> [Text] -> Sql92InsertValuesSyntax PgInsertSyntax -> PgInsertSyntax # | |
type Sql92InsertTableNameSyntax PgInsertSyntax Source # | |
type Sql92InsertValuesSyntax PgInsertSyntax Source # | |
newtype PgDeleteSyntax Source #
IsSql92DeleteSyntax
for Postgres
Constructors
PgDeleteSyntax | |
Fields |
Instances
IsSql92DeleteSyntax PgDeleteSyntax Source # | |
Defined in Database.Beam.Postgres.Syntax Associated Types | |
type Sql92DeleteExpressionSyntax PgDeleteSyntax Source # | |
type Sql92DeleteTableNameSyntax PgDeleteSyntax Source # | |
newtype PgUpdateSyntax Source #
IsSql92UpdateSyntax
for Postgres
Constructors
PgUpdateSyntax | |
Fields |
Instances
IsSql92UpdateSyntax PgUpdateSyntax Source # | |
Defined in Database.Beam.Postgres.Syntax Associated Types type Sql92UpdateTableNameSyntax PgUpdateSyntax # | |
type Sql92UpdateExpressionSyntax PgUpdateSyntax Source # | |
type Sql92UpdateFieldNameSyntax PgUpdateSyntax Source # | |
type Sql92UpdateTableNameSyntax PgUpdateSyntax Source # | |
newtype PgExpressionSyntax Source #
Constructors
PgExpressionSyntax | |
Fields |
Instances
newtype PgFromSyntax Source #
Constructors
PgFromSyntax | |
Fields |
Instances
IsSql92FromOuterJoinSyntax PgFromSyntax Source # | |
Defined in Database.Beam.Postgres.Syntax Methods outerJoin :: PgFromSyntax -> PgFromSyntax -> Maybe (Sql92FromExpressionSyntax PgFromSyntax) -> PgFromSyntax # | |
IsSql92FromSyntax PgFromSyntax Source # | |
Defined in Database.Beam.Postgres.Syntax Associated Types Methods fromTable :: Sql92FromTableSourceSyntax PgFromSyntax -> Maybe (Text, Maybe [Text]) -> PgFromSyntax # innerJoin :: PgFromSyntax -> PgFromSyntax -> Maybe (Sql92FromExpressionSyntax PgFromSyntax) -> PgFromSyntax # leftJoin :: PgFromSyntax -> PgFromSyntax -> Maybe (Sql92FromExpressionSyntax PgFromSyntax) -> PgFromSyntax # rightJoin :: PgFromSyntax -> PgFromSyntax -> Maybe (Sql92FromExpressionSyntax PgFromSyntax) -> PgFromSyntax # | |
type Sql92FromExpressionSyntax PgFromSyntax Source # | |
Defined in Database.Beam.Postgres.Syntax | |
type Sql92FromTableSourceSyntax PgFromSyntax Source # | |
newtype PgTableNameSyntax Source #
Constructors
PgTableNameSyntax | |
Fields |
Instances
newtype PgComparisonQuantifierSyntax Source #
Constructors
PgComparisonQuantifierSyntax | |
Fields |
newtype PgExtractFieldSyntax Source #
Constructors
PgExtractFieldSyntax | |
Fields |
Instances
newtype PgProjectionSyntax Source #
Constructors
PgProjectionSyntax | |
Fields |
Instances
IsSql92ProjectionSyntax PgProjectionSyntax Source # | |
Defined in Database.Beam.Postgres.Syntax Associated Types Methods projExprs :: [(Sql92ProjectionExpressionSyntax PgProjectionSyntax, Maybe Text)] -> PgProjectionSyntax # | |
type Sql92ProjectionExpressionSyntax PgProjectionSyntax Source # | |
newtype PgGroupingSyntax Source #
Constructors
PgGroupingSyntax | |
Fields |
Instances
IsSql92GroupingSyntax PgGroupingSyntax Source # | |
Defined in Database.Beam.Postgres.Syntax Associated Types | |
type Sql92GroupingExpressionSyntax PgGroupingSyntax Source # | |
data PgOrderingSyntax Source #
Constructors
PgOrderingSyntax | |
Fields
|
Instances
IsSql2003OrderingElementaryOLAPOperationsSyntax PgOrderingSyntax Source # | |
Defined in Database.Beam.Postgres.Syntax | |
IsSql92OrderingSyntax PgOrderingSyntax Source # | |
Defined in Database.Beam.Postgres.Syntax Associated Types | |
type Sql92OrderingExpressionSyntax PgOrderingSyntax Source # | |
newtype PgValueSyntax Source #
Constructors
PgValueSyntax | |
Fields |
Instances
newtype PgTableSourceSyntax Source #
Constructors
PgTableSourceSyntax | |
Fields |
Instances
newtype PgFieldNameSyntax Source #
Constructors
PgFieldNameSyntax | |
Fields |
Instances
IsSql92FieldNameSyntax PgFieldNameSyntax Source # | |
Defined in Database.Beam.Postgres.Syntax Methods qualifiedField :: Text -> Text -> PgFieldNameSyntax # |
newtype PgAggregationSetQuantifierSyntax Source #
Constructors
PgAggregationSetQuantifierSyntax | |
Fields |
newtype PgInsertValuesSyntax Source #
Constructors
PgInsertValuesSyntax | |
Fields |
Instances
newtype PgInsertOnConflictSyntax Source #
Constructors
PgInsertOnConflictSyntax | |
Fields |
newtype PgInsertOnConflictTargetSyntax Source #
Constructors
PgInsertOnConflictTargetSyntax | |
Fields |
newtype PgConflictActionSyntax Source #
Constructors
PgConflictActionSyntax | |
Fields |
newtype PgCreateTableSyntax Source #
Constructors
PgCreateTableSyntax | |
Fields |
Instances
data PgTableOptionsSyntax Source #
Constructors
PgTableOptionsSyntax PgSyntax PgSyntax |
newtype PgColumnSchemaSyntax Source #
Constructors
PgColumnSchemaSyntax | |
Fields |
Instances
Show PgColumnSchemaSyntax Source # | |
Defined in Database.Beam.Postgres.Syntax Methods showsPrec :: Int -> PgColumnSchemaSyntax -> ShowS # show :: PgColumnSchemaSyntax -> String # showList :: [PgColumnSchemaSyntax] -> ShowS # | |
Sql92DisplaySyntax PgColumnSchemaSyntax Source # | |
Defined in Database.Beam.Postgres.Syntax Methods | |
IsSql92ColumnSchemaSyntax PgColumnSchemaSyntax Source # | |
Eq PgColumnSchemaSyntax Source # | |
Defined in Database.Beam.Postgres.Syntax Methods (==) :: PgColumnSchemaSyntax -> PgColumnSchemaSyntax -> Bool # (/=) :: PgColumnSchemaSyntax -> PgColumnSchemaSyntax -> Bool # | |
Hashable PgColumnSchemaSyntax Source # | |
Defined in Database.Beam.Postgres.Syntax | |
type Sql92ColumnSchemaColumnConstraintDefinitionSyntax PgColumnSchemaSyntax Source # | |
type Sql92ColumnSchemaColumnTypeSyntax PgColumnSchemaSyntax Source # | |
type Sql92ColumnSchemaExpressionSyntax PgColumnSchemaSyntax Source # | |
data PgDataTypeSyntax Source #
Constructors
PgDataTypeSyntax | |
Instances
data PgColumnConstraintDefinitionSyntax Source #
Constructors
PgColumnConstraintDefinitionSyntax | |
Instances
data PgColumnConstraintSyntax Source #
Constructors
PgColumnConstraintSyntax | |
Instances
data PgReferentialActionSyntax Source #
Constructors
PgReferentialActionSyntax | |
newtype PgAlterTableSyntax Source #
Constructors
PgAlterTableSyntax | |
Fields |
Instances
newtype PgAlterTableActionSyntax Source #
Constructors
PgAlterTableActionSyntax | |
Fields |
Instances
newtype PgWindowFrameSyntax Source #
Constructors
PgWindowFrameSyntax | |
Fields |
Instances
newtype PgWindowFrameBoundsSyntax Source #
Constructors
PgWindowFrameBoundsSyntax | |
Fields |
Instances
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 |
Instances
data PgSelectLockingOptions Source #
Specifies how we should handle lock conflicts.
See the manual section for more information
Constructors
PgSelectLockingOptionsNoWait |
|
PgSelectLockingOptionsSkipLocked |
|
Instances
Arguments
:: PgSelectTableSyntax | |
-> [PgOrderingSyntax] | |
-> Maybe Integer | LIMIT |
-> Maybe Integer | OFFSET |
-> Maybe PgSelectLockingClauseSyntax | |
-> PgSelectSyntax |
defaultPgValueSyntax :: ToField a => a -> PgValueSyntax Source #
data PgDataTypeDescr Source #
Constructors
PgDataTypeDescrOid Oid (Maybe Int32) | |
PgDataTypeDescrDomain Text |
Instances
Instances
Generic PgHasEnum Source # | |
Show PgHasEnum Source # | |
DatabasePredicate PgHasEnum Source # | |
Defined in Database.Beam.Postgres.Syntax Methods englishDescription :: PgHasEnum -> String # predicateSpecificity :: proxy PgHasEnum -> PredicateSpecificity # serializePredicate :: PgHasEnum -> Value # predicateCascadesDropOn :: DatabasePredicate p' => PgHasEnum -> p' -> Bool # | |
Eq PgHasEnum Source # | |
Hashable PgHasEnum Source # | |
Defined in Database.Beam.Postgres.Syntax | |
type Rep PgHasEnum Source # | |
Defined in Database.Beam.Postgres.Syntax type Rep PgHasEnum = D1 ('MetaData "PgHasEnum" "Database.Beam.Postgres.Syntax" "beam-postgres-0.5.3.0-6PBRjXa9eUb6sY3XEHVcT4" 'False) (C1 ('MetaCons "PgHasEnum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text]))) |
pgCreateEnumSyntax :: Text -> [PgValueSyntax] -> PgCommandSyntax Source #
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 #