sqel-0.0.1.0: Guided derivation for Hasql statements
Safe HaskellSafe-Inferred
LanguageHaskell2010

Sqel.Data.Migration

Documentation

data MigrationActions ext Source #

Instances

Instances details
Generic (MigrationActions ext) Source # 
Instance details

Defined in Sqel.Data.Migration

Associated Types

type Rep (MigrationActions ext) :: Type -> Type #

type Rep (MigrationActions ext) Source # 
Instance details

Defined in Sqel.Data.Migration

type Rep (MigrationActions ext) = D1 ('MetaData "MigrationActions" "Sqel.Data.Migration" "sqel-0.0.1.0-5k4czMecwS553bFrfF1Jzu" 'False) (C1 ('MetaCons "AutoActions" 'PrefixI 'True) (S1 ('MetaSel ('Just "table") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TableAction) :*: S1 ('MetaSel ('Just "types") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map PgCompName CompAction))) :+: C1 ('MetaCons "CustomActions" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ext)))

data Mig Source #

Constructors

Mig 

Fields

Instances

Instances details
HoistMigrations m n ('[] :: [Mig]) ('[] :: [Mig]) Source # 
Instance details

Defined in Sqel.Data.Migration

Methods

hoistMigrations :: (forall x. m x -> n x) -> Migrations m '[] -> Migrations n '[] Source #

(HoistMigration m n ext ext', HoistMigrations m n migs migs') => HoistMigrations m n ('Mig from to m ext ': migs) ('Mig from to n ext' ': migs') Source # 
Instance details

Defined in Sqel.Data.Migration

Methods

hoistMigrations :: (forall x. m x -> n x) -> Migrations m ('Mig from to m ext ': migs) -> Migrations n ('Mig from to n ext' ': migs') Source #

MkMigrations (Migration ('Mig from to m ext)) '['Mig from to m ext] Source # 
Instance details

Defined in Sqel.Data.Migration

Methods

mkMigrations :: Migration ('Mig from to m ext) -> NP Migration '['Mig from to m ext] Source #

MkMigrations old (mig1 ': migs) => MkMigrations (Migration ('Mig from to m ext) :> old) ('Mig from to m ext ': (mig1 ': migs)) Source # 
Instance details

Defined in Sqel.Data.Migration

Methods

mkMigrations :: (Migration ('Mig from to m ext) :> old) -> NP Migration ('Mig from to m ext ': (mig1 ': migs)) Source #

data Migration t where Source #

Constructors

Migration 

Fields

Instances

Instances details
MkMigrations (Migration ('Mig from to m ext)) '['Mig from to m ext] Source # 
Instance details

Defined in Sqel.Data.Migration

Methods

mkMigrations :: Migration ('Mig from to m ext) -> NP Migration '['Mig from to m ext] Source #

MkMigrations old (mig1 ': migs) => MkMigrations (Migration ('Mig from to m ext) :> old) ('Mig from to m ext ': (mig1 ': migs)) Source # 
Instance details

Defined in Sqel.Data.Migration

Methods

mkMigrations :: (Migration ('Mig from to m ext) :> old) -> NP Migration ('Mig from to m ext ': (mig1 ': migs)) Source #

type family MigFrom (mig :: Mig) :: Type where ... Source #

Equations

MigFrom ('Mig from _ _ _) = from 

type family MigTo (mig :: Mig) :: Type where ... Source #

Equations

MigTo ('Mig _ to _ _) = to 

type family MigEff (mig :: Mig) :: Type -> Type where ... Source #

Equations

MigEff ('Mig _ _ m _) = m 

type family MigExt (mig :: Mig) :: Type where ... Source #

Equations

MigExt ('Mig _ _ _ ext) = ext 

type family UniMigList m ext as where ... Source #

Equations

UniMigList _ _ '[] = '[] 
UniMigList m ext [new, old] = '['Mig old new m ext] 
UniMigList m ext (new ': (old ': as)) = 'Mig old new m ext ': UniMigList m ext (old ': as) 

type family UniMigs m ext old cur where ... Source #

Equations

UniMigs _ _ '[] _ = '[] 
UniMigs m ext '[o] cur = '['Mig o cur m ext] 
UniMigs m ext (o ': os) cur = 'Mig o cur m ext ': UniMigList m ext (o ': os) 

newtype Migrations m migs Source #

Constructors

Migrations 

Fields

type UniMigrations m ext old cur = Migrations m (UniMigs m ext old cur) Source #

type AutoMigrations m old cur = UniMigrations m Void old cur Source #

class MkMigrations arg migs | arg -> migs, migs -> arg where Source #

Methods

mkMigrations :: arg -> NP Migration migs Source #

Instances

Instances details
MkMigrations (Migration ('Mig from to m ext)) '['Mig from to m ext] Source # 
Instance details

Defined in Sqel.Data.Migration

Methods

mkMigrations :: Migration ('Mig from to m ext) -> NP Migration '['Mig from to m ext] Source #

MkMigrations old (mig1 ': migs) => MkMigrations (Migration ('Mig from to m ext) :> old) ('Mig from to m ext ': (mig1 ': migs)) Source # 
Instance details

Defined in Sqel.Data.Migration

Methods

mkMigrations :: (Migration ('Mig from to m ext) :> old) -> NP Migration ('Mig from to m ext ': (mig1 ': migs)) Source #

migrate :: MkMigrations arg migs => arg -> Migrations m migs Source #

class CustomMigration m mig where Source #

Instances

Instances details
CustomMigration m ('Mig from to m Void) Source # 
Instance details

Defined in Sqel.Data.Migration

Methods

customTypeKeys :: MigExt ('Mig from to m Void) -> m (Set (PgCompName, Bool)) Source #

customMigration :: PgTableName -> Set PgCompName -> MigExt ('Mig from to m Void) -> m () Source #

(Monad m, MigrationEffect m) => CustomMigration m ('Mig old new m (MigrateTransform m old new)) Source # 
Instance details

Defined in Sqel.Migration.Transform

Methods

customTypeKeys :: MigExt ('Mig old new m (MigrateTransform m old new)) -> m (Set (PgCompName, Bool)) Source #

customMigration :: PgTableName -> Set PgCompName -> MigExt ('Mig old new m (MigrateTransform m old new)) -> m () Source #

class HoistMigration m n ext ext' | m n ext -> ext' where Source #

Methods

hoistMigration :: (forall x. m x -> n x) -> ext -> ext' Source #

Instances

Instances details
HoistMigration (m :: k -> Type) (n :: k -> Type) Void Void Source # 
Instance details

Defined in Sqel.Data.Migration

Methods

hoistMigration :: (forall (x :: k0). m x -> n x) -> Void -> Void Source #

class HoistMigrations m n migs migs' | m n migs -> migs' where Source #

Methods

hoistMigrations :: (forall x. m x -> n x) -> Migrations m migs -> Migrations n migs' Source #

Instances

Instances details
HoistMigrations m n ('[] :: [Mig]) ('[] :: [Mig]) Source # 
Instance details

Defined in Sqel.Data.Migration

Methods

hoistMigrations :: (forall x. m x -> n x) -> Migrations m '[] -> Migrations n '[] Source #

(HoistMigration m n ext ext', HoistMigrations m n migs migs') => HoistMigrations m n ('Mig from to m ext ': migs) ('Mig from to n ext' ': migs') Source # 
Instance details

Defined in Sqel.Data.Migration

Methods

hoistMigrations :: (forall x. m x -> n x) -> Migrations m ('Mig from to m ext ': migs) -> Migrations n ('Mig from to n ext' ': migs') Source #