Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Contains a schema for beam migration tools. Used by the CLI and the managed migrations support here.
Documentation
LogEntry | |
|
Instances
Show LogEntry Source # | |
Show LogEntryKey Source # | |
Defined in Database.Beam.Migrate.Log showsPrec :: Int -> LogEntryKey -> ShowS # show :: LogEntryKey -> String # showList :: [LogEntryKey] -> ShowS # | |
Beamable LogEntryT Source # | |
Defined in Database.Beam.Migrate.Log zipBeamFieldsM :: forall m (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type). Applicative m => (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a)) -> LogEntryT f -> LogEntryT g -> m (LogEntryT h) tblSkeleton :: TableSkeleton LogEntryT | |
Table LogEntryT Source # | |
Defined in Database.Beam.Migrate.Log data PrimaryKey LogEntryT column primaryKey :: forall (column :: Type -> Type). LogEntryT column -> PrimaryKey LogEntryT column | |
Generic (LogEntryT f) Source # | |
Beamable (PrimaryKey LogEntryT) Source # | |
Defined in Database.Beam.Migrate.Log zipBeamFieldsM :: forall m (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type). Applicative m => (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a)) -> PrimaryKey LogEntryT f -> PrimaryKey LogEntryT g -> m (PrimaryKey LogEntryT h) tblSkeleton :: TableSkeleton (PrimaryKey LogEntryT) | |
Generic (PrimaryKey LogEntryT f) Source # | |
data PrimaryKey LogEntryT f Source # | |
Defined in Database.Beam.Migrate.Log | |
type Rep (LogEntryT f) Source # | |
Defined in Database.Beam.Migrate.Log type Rep (LogEntryT f) = D1 ('MetaData "LogEntryT" "Database.Beam.Migrate.Log" "beam-migrate-0.5.2.0-inplace" 'False) (C1 ('MetaCons "LogEntry" 'PrefixI 'True) (S1 ('MetaSel ('Just "_logEntryId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (C f Int32)) :*: (S1 ('MetaSel ('Just "_logEntryCommitId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (C f Text)) :*: S1 ('MetaSel ('Just "_logEntryDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (C f LocalTime))))) | |
type Rep (PrimaryKey LogEntryT f) Source # | |
Defined in Database.Beam.Migrate.Log |
type LogEntryKey = PrimaryKey LogEntryT Identity Source #
newtype BeamMigrateVersionT f Source #
Instances
type BeamMigrateVersionKey = PrimaryKey BeamMigrateVersionT Identity Source #
data BeamMigrateDb entity Source #
BeamMigrateDb | |
|
Instances
Database be BeamMigrateDb Source # | |
Defined in Database.Beam.Migrate.Log zipTables :: Applicative m => Proxy be -> (forall tbl. (IsDatabaseEntity be tbl, DatabaseEntityRegularRequirements be tbl) => f tbl -> g tbl -> m (h tbl)) -> BeamMigrateDb f -> BeamMigrateDb g -> m (BeamMigrateDb h) | |
Generic (BeamMigrateDb entity) Source # | |
Defined in Database.Beam.Migrate.Log type Rep (BeamMigrateDb entity) :: Type -> Type # from :: BeamMigrateDb entity -> Rep (BeamMigrateDb entity) x # to :: Rep (BeamMigrateDb entity) x -> BeamMigrateDb entity # | |
type Rep (BeamMigrateDb entity) Source # | |
Defined in Database.Beam.Migrate.Log type Rep (BeamMigrateDb entity) = D1 ('MetaData "BeamMigrateDb" "Database.Beam.Migrate.Log" "beam-migrate-0.5.2.0-inplace" 'False) (C1 ('MetaCons "BeamMigrateDb" 'PrefixI 'True) (S1 ('MetaSel ('Just "_beamMigrateVersionTbl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (entity (TableEntity BeamMigrateVersionT))) :*: S1 ('MetaSel ('Just "_beamMigrateLogEntries") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (entity (TableEntity LogEntryT))))) |
beamMigratableDb :: forall be m. (BeamMigrateSqlBackend be, HasDataTypeCreatedCheck (BeamMigrateSqlBackendDataTypeSyntax be), MonadBeam be m) => CheckedDatabaseSettings be BeamMigrateDb Source #
beamMigrateDb :: forall be m. (BeamMigrateSqlBackend be, HasDataTypeCreatedCheck (BeamMigrateSqlBackendDataTypeSyntax be), MonadBeam be m) => DatabaseSettings be BeamMigrateDb Source #
beamMigrateDbMigration :: forall be m. (BeamMigrateSqlBackend be, HasDataTypeCreatedCheck (BeamMigrateSqlBackendDataTypeSyntax be), MonadBeam be m) => Migration be (CheckedDatabaseSettings be BeamMigrateDb) Source #
getLatestLogEntry :: forall be m. (BeamMigrateSqlBackend be, HasDataTypeCreatedCheck (BeamMigrateSqlBackendDataTypeSyntax be), BeamSqlBackendCanDeserialize be Int32, BeamSqlBackendCanDeserialize be LocalTime, BeamSqlBackendSupportsDataType be Text, HasQBuilder be, MonadBeam be m) => m (Maybe LogEntry) Source #
updateSchemaToCurrent :: forall be m. (BeamMigrateSqlBackend be, HasDataTypeCreatedCheck (BeamMigrateSqlBackendDataTypeSyntax be), BeamSqlBackendCanSerialize be Text, MonadBeam be m) => m () Source #
recordCommit :: forall be m. (BeamMigrateSqlBackend be, HasDataTypeCreatedCheck (BeamMigrateSqlBackendDataTypeSyntax be), BeamSqlBackendSupportsDataType be Text, BeamSqlBackendCanDeserialize be Int32, BeamSqlBackendCanDeserialize be LocalTime, HasQBuilder be, MonadBeam be m) => UUID -> m () Source #
ensureBackendTables :: forall be m. (BeamSqlBackendCanSerialize be Text, MonadFail m) => BeamMigrationBackend be m -> m () Source #
checkForBackendTables :: BeamMigrationBackend be m -> m Bool Source #