| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Sqel.Migration.Type
Documentation
Instances
| ReifyActions ('[] :: [ActionK]) ('[] :: [DdlTypeK]) new Source # | |
Defined in Sqel.Migration.Type Methods reifyActions :: NP DdlType '[] -> NP DdlType new -> [(PgCompName, CompAction)] Source # | |
| (ReifyNewAction action new, ReifyActions actions ('[] :: [DdlTypeK]) new) => ReifyActions (action ': actions) ('[] :: [DdlTypeK]) new Source # | |
Defined in Sqel.Migration.Type Methods reifyActions :: NP DdlType '[] -> NP DdlType new -> [(PgCompName, CompAction)] Source # | |
| (ReifyOldAction 'False action o new, ReifyActions actions old new) => ReifyActions (action ': actions) (o ': old) new Source # | |
Defined in Sqel.Migration.Type Methods reifyActions :: NP DdlType (o ': old) -> NP DdlType new -> [(PgCompName, CompAction)] Source # | |
type family MkMigrationAction (old :: OldK) (check :: [NewK]) (other :: [NewK]) :: (ActionK, [NewK]) where ... Source #
Equations
| MkMigrationAction _ '[] other = '('UnusedK, other) | |
| MkMigrationAction ('OldK table name _) ('NewK index table name 'Nothing _ ': news) other = '('ActionK 'KeepK index, news ++ other) | |
| MkMigrationAction ('OldK table oldName _) ('NewK index table _ ('Just oldName) _ ': news) other = '('ActionK 'RenameK index, news ++ other) | |
| MkMigrationAction old (new ': news) other = MkMigrationAction old news (new ': other) |
type family NewMigrationActions (cols :: [NewK]) :: [ActionK] where ... Source #
Equations
| NewMigrationActions '[] = '[] | |
| NewMigrationActions ('NewK index 'False _ 'Nothing _ ': news) = 'ActionK 'AddK index ': NewMigrationActions news | |
| NewMigrationActions cols = TypeError ("type NewMigrationActions:" % cols) |
type family MigrationActionsCont (cur :: (ActionK, [NewK])) (old :: [OldK]) :: [ActionK] where ... Source #
Equations
| MigrationActionsCont '(cur, new) old = cur ': MigrationActions old new |
type family MigrationActions (old :: [OldK]) (new :: [NewK]) :: [ActionK] where ... Source #
Equations
| MigrationActions '[] rest = NewMigrationActions rest | |
| MigrationActions (old ': olds) new = MigrationActionsCont (MkMigrationAction old new '[]) olds |
class ReifyKeepAction table old new where Source #
Methods
reifyKeepAction :: DdlType old -> DdlType new -> TypeAction table Source #
Instances
| ColumnsChanges colsOld colsNew => ReifyKeepAction table ('DdlTypeK table tname renameOld colsOld) ('DdlTypeK table tname renameNew colsNew) Source # | |
Defined in Sqel.Migration.Type Methods reifyKeepAction :: DdlType ('DdlTypeK table tname renameOld colsOld) -> DdlType ('DdlTypeK table tname renameNew colsNew) -> TypeAction table Source # | |
type family ReifyModResult (table :: Bool) :: Type where ... Source #
Equations
| ReifyModResult 'False = [(PgCompName, CompAction)] | |
| ReifyModResult 'True = TypeAction 'True |
class ReifyModAction table action old new where Source #
Methods
reifyModAction :: DdlType old -> DdlType new -> ReifyModResult table Source #
Instances
| ReifyKeepAction 'True old new => ReifyModAction 'True 'KeepK old new Source # | |
Defined in Sqel.Migration.Type Methods reifyModAction :: DdlType old -> DdlType new -> ReifyModResult 'True Source # | |
| ReifyKeepAction 'False ('DdlTypeK 'False tname renameOld colsOld) new => ReifyModAction 'False 'KeepK ('DdlTypeK 'False tname renameOld colsOld) new Source # | |
Defined in Sqel.Migration.Type Methods reifyModAction :: DdlType ('DdlTypeK 'False tname renameOld colsOld) -> DdlType new -> ReifyModResult 'False Source # | |
| ColumnsChanges colsOld colsNew => ReifyModAction 'False 'RenameK ('DdlTypeK 'False name renameOld colsOld) ('DdlTypeK 'False nameNew ('Just name) colsNew) Source # | |
Defined in Sqel.Migration.Type | |
class ReifyOldAction table action old new where Source #
Methods
reifyOldAction :: DdlType old -> NP DdlType new -> ReifyModResult table Source #
Instances
| ReifyOldAction 'False 'UnusedK ('DdlTypeK 'False name renameOld colsOld) new Source # | |
Defined in Sqel.Migration.Type Methods reifyOldAction :: DdlType ('DdlTypeK 'False name renameOld colsOld) -> NP DdlType new -> ReifyModResult 'False Source # | |
| (ColIndex index news new, ReifyModAction table mod old new) => ReifyOldAction table ('ActionK mod index) old news Source # | |
Defined in Sqel.Migration.Type Methods reifyOldAction :: DdlType old -> NP DdlType news -> ReifyModResult table Source # | |
class ReifyNewAction action new where Source #
Methods
reifyNewAction :: NP DdlType new -> (PgCompName, CompAction) Source #
Instances
| (SListI cols, ColIndex index news ('DdlTypeK 'False name rename cols)) => ReifyNewAction ('ActionK 'AddK index) news Source # | |
Defined in Sqel.Migration.Type Methods reifyNewAction :: NP DdlType news -> (PgCompName, CompAction) Source # | |
class ReifyActions actions old new where Source #
Methods
reifyActions :: NP DdlType old -> NP DdlType new -> [(PgCompName, CompAction)] Source #
Instances
| ReifyActions ('[] :: [ActionK]) ('[] :: [DdlTypeK]) new Source # | |
Defined in Sqel.Migration.Type Methods reifyActions :: NP DdlType '[] -> NP DdlType new -> [(PgCompName, CompAction)] Source # | |
| (ReifyNewAction action new, ReifyActions actions ('[] :: [DdlTypeK]) new) => ReifyActions (action ': actions) ('[] :: [DdlTypeK]) new Source # | |
Defined in Sqel.Migration.Type Methods reifyActions :: NP DdlType '[] -> NP DdlType new -> [(PgCompName, CompAction)] Source # | |
| (ReifyOldAction 'False action o new, ReifyActions actions old new) => ReifyActions (action ': actions) (o ': old) new Source # | |
Defined in Sqel.Migration.Type Methods reifyActions :: NP DdlType (o ': old) -> NP DdlType new -> [(PgCompName, CompAction)] Source # | |
class TypeChanges old new where Source #
Methods
typeChanges :: NP DdlType old -> NP DdlType new -> [(PgCompName, CompAction)] Source #
Instances
| (actions ~ MigrationActions (OldKs 0 old) (NewKs 0 new), ReifyActions actions old new) => TypeChanges old new Source # | |
Defined in Sqel.Migration.Type Methods typeChanges :: NP DdlType old -> NP DdlType new -> [(PgCompName, CompAction)] Source # | |
class TableChange old new where Source #
Methods
tableChange :: DdlType old -> DdlType new -> TableAction Source #
Instances
| ('[oldk] ~ OldKs 0 '[old], '(action, '[] :: [NewK]) ~ MkMigrationAction oldk (NewKs 0 '[new]) ('[] :: [NewK]), ReifyOldAction 'True action old '[new]) => TableChange old new Source # | |
Defined in Sqel.Migration.Type Methods tableChange :: DdlType old -> DdlType new -> TableAction Source # | |