beam-migrate-0.5.2.1: SQL DDL support and migrations support library for Beam
Safe HaskellSafe-Inferred
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

Instances details
Show LogEntry Source # 
Instance details

Defined in Database.Beam.Migrate.Log

Show LogEntryKey Source # 
Instance details

Defined in Database.Beam.Migrate.Log

Beamable LogEntryT Source # 
Instance details

Defined in Database.Beam.Migrate.Log

Methods

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 # 
Instance details

Defined in Database.Beam.Migrate.Log

Associated Types

data PrimaryKey LogEntryT column #

Methods

primaryKey :: forall (column :: Type -> Type). LogEntryT column -> PrimaryKey LogEntryT column #

Generic (LogEntryT f) Source # 
Instance details

Defined in Database.Beam.Migrate.Log

Associated Types

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

Methods

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

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

Beamable (PrimaryKey LogEntryT) Source # 
Instance details

Defined in Database.Beam.Migrate.Log

Methods

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 # 
Instance details

Defined in Database.Beam.Migrate.Log

Associated Types

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

data PrimaryKey LogEntryT f Source # 
Instance details

Defined in Database.Beam.Migrate.Log

type Rep (LogEntryT f) Source # 
Instance details

Defined in Database.Beam.Migrate.Log

type Rep (LogEntryT f) = D1 ('MetaData "LogEntryT" "Database.Beam.Migrate.Log" "beam-migrate-0.5.2.1-9bdNI0guWCXI96qZbaP2Bw" '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 # 
Instance details

Defined in Database.Beam.Migrate.Log

type Rep (PrimaryKey LogEntryT f) = D1 ('MetaData "PrimaryKey" "Database.Beam.Migrate.Log" "beam-migrate-0.5.2.1-9bdNI0guWCXI96qZbaP2Bw" 'False) (C1 ('MetaCons "LogEntryKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (C f Int32))))

newtype BeamMigrateVersionT f Source #

Constructors

BeamMigrateVersion 

Instances

Instances details
Show BeamMigrateVersion Source # 
Instance details

Defined in Database.Beam.Migrate.Log

Show BeamMigrateVersionKey Source # 
Instance details

Defined in Database.Beam.Migrate.Log

Beamable BeamMigrateVersionT Source # 
Instance details

Defined in Database.Beam.Migrate.Log

Methods

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)) -> BeamMigrateVersionT f -> BeamMigrateVersionT g -> m (BeamMigrateVersionT h) #

tblSkeleton :: TableSkeleton BeamMigrateVersionT #

Table BeamMigrateVersionT Source # 
Instance details

Defined in Database.Beam.Migrate.Log

Associated Types

data PrimaryKey BeamMigrateVersionT column #

Methods

primaryKey :: forall (column :: Type -> Type). BeamMigrateVersionT column -> PrimaryKey BeamMigrateVersionT column #

Generic (BeamMigrateVersionT f) Source # 
Instance details

Defined in Database.Beam.Migrate.Log

Associated Types

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

Beamable (PrimaryKey BeamMigrateVersionT) Source # 
Instance details

Defined in Database.Beam.Migrate.Log

Generic (PrimaryKey BeamMigrateVersionT f) Source # 
Instance details

Defined in Database.Beam.Migrate.Log

Associated Types

type Rep (PrimaryKey BeamMigrateVersionT f) :: Type -> Type #

data PrimaryKey BeamMigrateVersionT f Source # 
Instance details

Defined in Database.Beam.Migrate.Log

type Rep (BeamMigrateVersionT f) Source # 
Instance details

Defined in Database.Beam.Migrate.Log

type Rep (BeamMigrateVersionT f) = D1 ('MetaData "BeamMigrateVersionT" "Database.Beam.Migrate.Log" "beam-migrate-0.5.2.1-9bdNI0guWCXI96qZbaP2Bw" 'True) (C1 ('MetaCons "BeamMigrateVersion" 'PrefixI 'True) (S1 ('MetaSel ('Just "_beamMigrateVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (C f Int32))))
type Rep (PrimaryKey BeamMigrateVersionT f) Source # 
Instance details

Defined in Database.Beam.Migrate.Log

type Rep (PrimaryKey BeamMigrateVersionT f) = D1 ('MetaData "PrimaryKey" "Database.Beam.Migrate.Log" "beam-migrate-0.5.2.1-9bdNI0guWCXI96qZbaP2Bw" 'False) (C1 ('MetaCons "BeamMigrateVersionKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (C f Int32))))

data BeamMigrateDb entity Source #

Instances

Instances details
Database be BeamMigrateDb Source # 
Instance details

Defined in Database.Beam.Migrate.Log

Methods

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 # 
Instance details

Defined in Database.Beam.Migrate.Log

Associated Types

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

Methods

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

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

type Rep (BeamMigrateDb entity) Source # 
Instance details

Defined in Database.Beam.Migrate.Log

type Rep (BeamMigrateDb entity) = D1 ('MetaData "BeamMigrateDb" "Database.Beam.Migrate.Log" "beam-migrate-0.5.2.1-9bdNI0guWCXI96qZbaP2Bw" '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)))))