refurb-0.2.2.0: Tools for maintaining a database

Safe HaskellNone
LanguageHaskell2010

Refurb.Store

Description

Module containing definition of and functions for maintaining the in-database state storage for Refurb.

Synopsis

Documentation

type FId = (:->) "id" Int32 Source #

type FIdMay = (:->) "id" (Maybe Int32) Source #

type CId = (:->) "id" (Column PGInt4) Source #

type FQualifiedKey = (:->) "qualified_key" Text Source #

type CQualifiedKey = (:->) "qualified_key" (Column PGText) Source #

type FApplied = (:->) "applied" UTCTime Source #

type FOutput = (:->) "output" Text Source #

type COutput = (:->) "output" (Column PGText) Source #

type FDuration = (:->) "duration" Double Source #

type CDuration = (:->) "duration" (Column PGFloat8) Source #

type FProdSystem = (:->) "prod_system" Bool Source #

type CProdSystem = (:->) "prod_system" (Column PGBool) Source #

cProdSystem :: forall f rs. (Functor f, RElem CProdSystem rs (RIndex CProdSystem rs)) => (Column PGBool -> f (Column PGBool)) -> Record rs -> f (Record rs) Source #

fProdSystem :: forall f rs. (Functor f, RElem FProdSystem rs (RIndex FProdSystem rs)) => (Bool -> f Bool) -> Record rs -> f (Record rs) Source #

cDuration :: forall f rs. (Functor f, RElem CDuration rs (RIndex CDuration rs)) => (Column PGFloat8 -> f (Column PGFloat8)) -> Record rs -> f (Record rs) Source #

fDuration :: forall f rs. (Functor f, RElem FDuration rs (RIndex FDuration rs)) => (Double -> f Double) -> Record rs -> f (Record rs) Source #

cResult :: forall f rs. (Functor f, RElem CResult rs (RIndex CResult rs)) => (Column PGMigrationResult -> f (Column PGMigrationResult)) -> Record rs -> f (Record rs) Source #

fResult :: forall f rs. (Functor f, RElem FResult rs (RIndex FResult rs)) => (MigrationResult -> f MigrationResult) -> Record rs -> f (Record rs) Source #

cOutput :: forall f rs. (Functor f, RElem COutput rs (RIndex COutput rs)) => (Column PGText -> f (Column PGText)) -> Record rs -> f (Record rs) Source #

fOutput :: forall f rs. (Functor f, RElem FOutput rs (RIndex FOutput rs)) => (Text -> f Text) -> Record rs -> f (Record rs) Source #

cApplied :: forall f rs. (Functor f, RElem CApplied rs (RIndex CApplied rs)) => (Column PGTimestamptz -> f (Column PGTimestamptz)) -> Record rs -> f (Record rs) Source #

fApplied :: forall f rs. (Functor f, RElem FApplied rs (RIndex FApplied rs)) => (UTCTime -> f UTCTime) -> Record rs -> f (Record rs) Source #

cQualifiedKey :: forall f rs. (Functor f, RElem CQualifiedKey rs (RIndex CQualifiedKey rs)) => (Column PGText -> f (Column PGText)) -> Record rs -> f (Record rs) Source #

fQualifiedKey :: forall f rs. (Functor f, RElem FQualifiedKey rs (RIndex FQualifiedKey rs)) => (Text -> f Text) -> Record rs -> f (Record rs) Source #

cIdMay :: forall f rs. (Functor f, RElem CIdMay rs (RIndex CIdMay rs)) => (Maybe (Column PGInt4) -> f (Maybe (Column PGInt4))) -> Record rs -> f (Record rs) Source #

cId :: forall f rs. (Functor f, RElem CId rs (RIndex CId rs)) => (Column PGInt4 -> f (Column PGInt4)) -> Record rs -> f (Record rs) Source #

fIdMay :: forall f rs. (Functor f, RElem FIdMay rs (RIndex FIdMay rs)) => (Maybe Int32 -> f (Maybe Int32)) -> Record rs -> f (Record rs) Source #

fId :: forall f rs. (Functor f, RElem FId rs (RIndex FId rs)) => (Int32 -> f Int32) -> Record rs -> f (Record rs) Source #

type MigrationLog = '[FId, FQualifiedKey, FApplied, FOutput, FResult, FDuration] Source #

Fields of a migration log entry in memory fetched from the database (with ID)

type MigrationLogW = '[FIdMay, FQualifiedKey, FApplied, FOutput, FResult, FDuration] Source #

Fields of a migration log entry to insert in the database (with the ID column optional)

type MigrationLogColsR = '[CId, CQualifiedKey, CApplied, COutput, CResult, CDuration] Source #

Columns of a migration log when reading from the database (with ID)

type MigrationLogColsW = '[CIdMay, CQualifiedKey, CApplied, COutput, CResult, CDuration] Source #

Columns of a migration log when inserting into the database (with ID column optional)

type RefurbConfig = '[FProdSystem] Source #

Fields of the Refurb config in memory

type RefurbConfigCols = '[CProdSystem] Source #

Columns of the Refurb config in the database

migrationLog :: Table (Record MigrationLogColsW) (Record MigrationLogColsR) Source #

The migration log table which records all executed migrations and their results

refurbConfig :: Table (Record RefurbConfigCols) (Record RefurbConfigCols) Source #

The refurb config table which controls whether this database is considered a production one or not

isSchemaPresent :: (MonadBaseControl IO m, MonadMask m, MonadLogger m) => Connection -> m Bool Source #

Test to see if the schema seems to be installed by looking for an existing refurb_config table

isProdSystem :: (MonadBaseControl IO m, MonadLogger m) => Connection -> m Bool Source #

Check if this database is configured as a production database by reading the refurb config table

initializeSchema :: (MonadBaseControl IO m, MonadLogger m) => Connection -> m () Source #

Create the refurb schema elements. Will fail if they already exist.

readMigrationStatus :: (MonadBaseControl IO m, MonadLogger m) => Connection -> [Migration] -> QueryArr (Record MigrationLogColsR) () -> m [These Migration (Record MigrationLog)] Source #

Read the migration log and stitch it together with the expected migration list, forming a list in the same order as the known migrations but with These representing whether the migration log for the known migration is present or not.

  • This migration represents a known migration that has no log entry.
  • That migrationLog represents an unknown migration that was applied in the past.
  • These migration migrationLog represents a migration that has an attempted application in the log.