| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Database.Beam.Postgres.Migrate
Description
Migrations support for beam-postgres. See Database.Beam.Migrate for more information on beam migrations.
Synopsis
- data PgCommandSyntax
 - migrationBackend :: BeamMigrationBackend Postgres Pg
 - postgresDataTypeDeserializers :: BeamDeserializers Postgres
 - pgPredConverter :: HaskellPredicateConverter
 - getDbConstraints :: Connection -> IO [SomeDatabasePredicate]
 - getDbConstraintsForSchemas :: Maybe [String] -> Connection -> IO [SomeDatabasePredicate]
 - pgTypeToHs :: PgDataTypeSyntax -> Maybe HsDataType
 - migrateScript :: MigrationSteps Postgres () a' -> [ByteString]
 - writeMigrationScript :: FilePath -> MigrationSteps Postgres () a -> IO ()
 - pgDataTypeFromAtt :: ByteString -> Oid -> Maybe Int32 -> Maybe PgDataTypeSyntax
 - tsquery :: DataType Postgres TsQuery
 - tsvector :: DataType Postgres TsVector
 - text :: DataType Postgres Text
 - bytea :: DataType Postgres ByteString
 - unboundedArray :: forall a. Typeable a => DataType Postgres a -> DataType Postgres (Vector a)
 - uuid :: DataType Postgres UUID
 - money :: DataType Postgres PgMoney
 - json :: (ToJSON a, FromJSON a) => DataType Postgres (PgJSON a)
 - jsonb :: (ToJSON a, FromJSON a) => DataType Postgres (PgJSONB a)
 - smallserial :: Integral a => DataType Postgres (SqlSerial a)
 - serial :: Integral a => DataType Postgres (SqlSerial a)
 - bigserial :: Integral a => DataType Postgres (SqlSerial a)
 - point :: DataType Postgres PgPoint
 - line :: DataType Postgres PgLine
 - lineSegment :: DataType Postgres PgLineSegment
 - box :: DataType Postgres PgBox
 
Documentation
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.
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 Sql92UpdateSyntax 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 Sql92DdlCommandDropTableSyntax PgCommandSyntax Source # | |
| type Sql92DdlCommandAlterTableSyntax PgCommandSyntax Source # | |
| type Sql92DdlCommandCreateTableSyntax PgCommandSyntax Source # | |
migrationBackend :: BeamMigrationBackend Postgres Pg Source #
Top-level migration backend for use by beam-migrate tools
pgPredConverter :: HaskellPredicateConverter Source #
Converts postgres DatabasePredicates to DatabasePredicates in the
 Haskell syntax. Allows automatic generation of Haskell schemas from postgres
 constraints.
getDbConstraintsForSchemas :: Maybe [String] -> Connection -> IO [SomeDatabasePredicate] Source #
pgTypeToHs :: PgDataTypeSyntax -> Maybe HsDataType Source #
Turn a PgDataTypeSyntax into the corresponding HsDataType. This is a
 best effort guess, and may fail on more exotic types. Feel free to send PRs
 to make this function more robust!
migrateScript :: MigrationSteps Postgres () a' -> [ByteString] Source #
Turn a series of MigrationSteps into a line-by-line array of
 ByteStrings suitable for writing to a script.
writeMigrationScript :: FilePath -> MigrationSteps Postgres () a -> IO () Source #
Write the migration given by the MigrationSteps to a file.
pgDataTypeFromAtt :: ByteString -> Oid -> Maybe Int32 -> Maybe PgDataTypeSyntax Source #
Postgres data types
text :: DataType Postgres Text Source #
DataType for Postgres TEXT. characterLargeObject is also mapped to
 this data type
bytea :: DataType Postgres ByteString Source #
DataType for Postgres BYTEA. binaryLargeObject is also mapped to
 this data type
unboundedArray :: forall a. Typeable a => DataType Postgres a -> DataType Postgres (Vector a) Source #
DataType for a Postgres array without any bounds.
Note that array support in beam-migrate is still incomplete.
uuid :: DataType Postgres UUID Source #
DataType for UUID columns. The pgCryptoGenRandomUUID function in
 the PgCrypto extension can be used to generate UUIDs at random.
smallserial :: Integral a => DataType Postgres (SqlSerial a) Source #
Postgres SERIAL data types. Automatically generates an appropriate
 DEFAULT clause and sequence
serial :: Integral a => DataType Postgres (SqlSerial a) Source #
Postgres SERIAL data types. Automatically generates an appropriate
 DEFAULT clause and sequence
bigserial :: Integral a => DataType Postgres (SqlSerial a) Source #
Postgres SERIAL data types. Automatically generates an appropriate
 DEFAULT clause and sequence
Orphan instances
| BeamSqlBackendHasSerial Postgres Source # | |
Methods genericSerial :: FieldReturnType 'True 'False Postgres (SqlSerial Int) a => Text -> a #  | |