beam-migrate-0.3.0.0: SQL DDL support and migrations support library for Beam

Safe HaskellNone
LanguageHaskell2010

Database.Beam.Migrate.Log

Description

Contains a schema for beam migration tools. Used by the CLI and the managed migrations support here.

Documentation

data LogEntryT f Source #

Constructors

LogEntry 

Instances

Table LogEntryT Source # 

Associated Types

data PrimaryKey (LogEntryT :: (* -> *) -> *) (column :: * -> *) :: * #

Methods

primaryKey :: LogEntryT column -> PrimaryKey LogEntryT column #

Beamable LogEntryT Source # 

Methods

zipBeamFieldsM :: Applicative m => (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a)) -> LogEntryT f -> LogEntryT g -> m (LogEntryT h) #

tblSkeleton :: TableSkeleton LogEntryT #

Show (LogEntryT Identity) Source # 
Generic (LogEntryT f) Source # 

Associated Types

type Rep (LogEntryT f) :: * -> * #

Methods

from :: LogEntryT f -> Rep (LogEntryT f) x #

to :: Rep (LogEntryT f) x -> LogEntryT f #

Beamable (PrimaryKey LogEntryT) Source # 
Show (PrimaryKey LogEntryT Identity) Source # 
Generic (PrimaryKey LogEntryT f) Source # 

Associated Types

type Rep (PrimaryKey LogEntryT f) :: * -> * #

data PrimaryKey LogEntryT Source # 
type Rep (LogEntryT f) Source # 
type Rep (LogEntryT f) = D1 * (MetaData "LogEntryT" "Database.Beam.Migrate.Log" "beam-migrate-0.3.0.0-80nQ9E1UCic3KDYlVkYGFx" False) (C1 * (MetaCons "LogEntry" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_logEntryId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (C f Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "_logEntryCommitId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (C f Text))) (S1 * (MetaSel (Just Symbol "_logEntryDate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (C f LocalTime))))))
type Rep (PrimaryKey LogEntryT f) Source # 
type Rep (PrimaryKey LogEntryT f) = D1 * (MetaData "PrimaryKey" "Database.Beam.Migrate.Log" "beam-migrate-0.3.0.0-80nQ9E1UCic3KDYlVkYGFx" False) (C1 * (MetaCons "LogEntryKey" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (C f Int))))

newtype BeamMigrateVersionT f Source #

Constructors

BeamMigrateVersion 

Instances

Table BeamMigrateVersionT Source # 

Associated Types

data PrimaryKey (BeamMigrateVersionT :: (* -> *) -> *) (column :: * -> *) :: * #

Beamable BeamMigrateVersionT Source # 
Show (BeamMigrateVersionT Identity) Source # 
Generic (BeamMigrateVersionT f) Source # 

Associated Types

type Rep (BeamMigrateVersionT f) :: * -> * #

Beamable (PrimaryKey BeamMigrateVersionT) Source # 
Show (PrimaryKey BeamMigrateVersionT Identity) Source # 
Generic (PrimaryKey BeamMigrateVersionT f) Source # 
data PrimaryKey BeamMigrateVersionT Source # 
type Rep (BeamMigrateVersionT f) Source # 
type Rep (BeamMigrateVersionT f) = D1 * (MetaData "BeamMigrateVersionT" "Database.Beam.Migrate.Log" "beam-migrate-0.3.0.0-80nQ9E1UCic3KDYlVkYGFx" True) (C1 * (MetaCons "BeamMigrateVersion" PrefixI True) (S1 * (MetaSel (Just Symbol "_beamMigrateVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (C f Int))))
type Rep (PrimaryKey BeamMigrateVersionT f) Source # 
type Rep (PrimaryKey BeamMigrateVersionT f) = D1 * (MetaData "PrimaryKey" "Database.Beam.Migrate.Log" "beam-migrate-0.3.0.0-80nQ9E1UCic3KDYlVkYGFx" False) (C1 * (MetaCons "BeamMigrateVersionKey" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (C f Int))))

data BeamMigrateDb entity Source #

Instances

Database be BeamMigrateDb Source # 

Methods

zipTables :: Monad 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 # 

Associated Types

type Rep (BeamMigrateDb entity) :: * -> * #

Methods

from :: BeamMigrateDb entity -> Rep (BeamMigrateDb entity) x #

to :: Rep (BeamMigrateDb entity) x -> BeamMigrateDb entity #

type Rep (BeamMigrateDb entity) Source # 
type Rep (BeamMigrateDb entity) = D1 * (MetaData "BeamMigrateDb" "Database.Beam.Migrate.Log" "beam-migrate-0.3.0.0-80nQ9E1UCic3KDYlVkYGFx" False) (C1 * (MetaCons "BeamMigrateDb" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_beamMigrateVersionTbl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (entity (TableEntity BeamMigrateVersionT)))) (S1 * (MetaSel (Just Symbol "_beamMigrateLogEntries") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (entity (TableEntity LogEntryT))))))

ensureBackendTables :: forall be cmd hdl m. BeamMigrationBackend cmd be hdl m -> m () Source #