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

Sqel.Migration.Type

Documentation

data OldK Source #

Constructors

OldK 

Fields

data NewK Source #

Constructors

NewK 

Fields

data ModK Source #

Constructors

KeepK 
AddK 
RenameK 

data ActionK Source #

Constructors

ActionK 

Fields

UnusedK 

Instances

Instances details
ReifyActions ('[] :: [ActionK]) ('[] :: [DdlTypeK]) new Source # 
Instance details

Defined in Sqel.Migration.Type

(ReifyNewAction action new, ReifyActions actions ('[] :: [DdlTypeK]) new) => ReifyActions (action ': actions) ('[] :: [DdlTypeK]) new Source # 
Instance details

Defined in Sqel.Migration.Type

(ReifyOldAction 'False action o new, ReifyActions actions old new) => ReifyActions (action ': actions) (o ': old) new Source # 
Instance details

Defined in Sqel.Migration.Type

Methods

reifyActions :: NP DdlType (o ': old) -> NP DdlType new -> [(PgCompName, CompAction)] Source #

type family OldKs (index :: Nat) (types :: [DdlTypeK]) :: [OldK] where ... Source #

Equations

OldKs _ '[] = '[] 
OldKs index ('DdlTypeK table name _ cols ': types) = 'OldK table name cols ': OldKs (index + 1) types 

type family NewKs (index :: Nat) (types :: [DdlTypeK]) :: [NewK] where ... Source #

Equations

NewKs _ '[] = '[] 
NewKs index ('DdlTypeK table name rename cols ': types) = 'NewK index table name rename cols ': NewKs (index + 1) types 

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

Instances details
ColumnsChanges colsOld colsNew => ReifyKeepAction table ('DdlTypeK table tname renameOld colsOld) ('DdlTypeK table tname renameNew colsNew) Source # 
Instance details

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 #

class ReifyModAction table action old new where Source #

Methods

reifyModAction :: DdlType old -> DdlType new -> ReifyModResult table Source #

Instances

Instances details
ReifyKeepAction 'True old new => ReifyModAction 'True 'KeepK old new Source # 
Instance details

Defined in Sqel.Migration.Type

ReifyKeepAction 'False ('DdlTypeK 'False tname renameOld colsOld) new => ReifyModAction 'False 'KeepK ('DdlTypeK 'False tname renameOld colsOld) new Source # 
Instance details

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

Defined in Sqel.Migration.Type

Methods

reifyModAction :: DdlType ('DdlTypeK 'False name renameOld colsOld) -> DdlType ('DdlTypeK 'False nameNew ('Just name) colsNew) -> ReifyModResult 'False Source #

class ReifyOldAction table action old new where Source #

Methods

reifyOldAction :: DdlType old -> NP DdlType new -> ReifyModResult table Source #

Instances

Instances details
ReifyOldAction 'False 'UnusedK ('DdlTypeK 'False name renameOld colsOld) new Source # 
Instance details

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

Defined in Sqel.Migration.Type

Methods

reifyOldAction :: DdlType old -> NP DdlType news -> ReifyModResult table Source #

class ReifyNewAction action new where Source #

Instances

Instances details
(SListI cols, ColIndex index news ('DdlTypeK 'False name rename cols)) => ReifyNewAction ('ActionK 'AddK index) news Source # 
Instance details

Defined in Sqel.Migration.Type

class ReifyActions actions old new where Source #

Instances

Instances details
ReifyActions ('[] :: [ActionK]) ('[] :: [DdlTypeK]) new Source # 
Instance details

Defined in Sqel.Migration.Type

(ReifyNewAction action new, ReifyActions actions ('[] :: [DdlTypeK]) new) => ReifyActions (action ': actions) ('[] :: [DdlTypeK]) new Source # 
Instance details

Defined in Sqel.Migration.Type

(ReifyOldAction 'False action o new, ReifyActions actions old new) => ReifyActions (action ': actions) (o ': old) new Source # 
Instance details

Defined in Sqel.Migration.Type

Methods

reifyActions :: NP DdlType (o ': old) -> NP DdlType new -> [(PgCompName, CompAction)] Source #

class TypeChanges old new where Source #

Instances

Instances details
(actions ~ MigrationActions (OldKs 0 old) (NewKs 0 new), ReifyActions actions old new) => TypeChanges old new Source # 
Instance details

Defined in Sqel.Migration.Type

class TableChange old new where Source #

Methods

tableChange :: DdlType old -> DdlType new -> TableAction Source #

Instances

Instances details
('[oldk] ~ OldKs 0 '[old], '(action, '[] :: [NewK]) ~ MkMigrationAction oldk (NewKs 0 '[new]) ('[] :: [NewK]), ReifyOldAction 'True action old '[new]) => TableChange old new Source # 
Instance details

Defined in Sqel.Migration.Type

Methods

tableChange :: DdlType old -> DdlType new -> TableAction Source #