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

Sqel.Migration.Column

Documentation

data OldK Source #

Constructors

OldK 

Fields

data NewK Source #

Constructors

NewK 

data ModK Source #

Constructors

KeepK 
AddK 
RenameK 

data ActionK Source #

Constructors

ActionK 

Fields

RemoveK 

Instances

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

Defined in Sqel.Migration.Column

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

Defined in Sqel.Migration.Column

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

Defined in Sqel.Migration.Column

Methods

reifyActions :: NP DdlColumn (o ': old) -> NP DdlColumn new -> [ColumnAction] Source #

type family OldKs (index :: Nat) (cols :: [DdlColumnK]) :: [OldK] where ... Source #

Equations

OldKs _ '[] = '[] 
OldKs index ('DdlColumnK name comp _ _ _ delete _ ': cols) = 'OldK name comp delete ': OldKs (index + 1) cols 

type family NewKs (index :: Nat) (cols :: [DdlColumnK]) :: [NewK] where ... Source #

Equations

NewKs _ '[] = '[] 
NewKs index ('DdlColumnK name comp _ rename renameType _ _ ': cols) = 'NewK index name comp rename renameType ': NewKs (index + 1) cols 

type family MkMigrationAction (old :: OldK) (check :: [NewK]) (other :: [NewK]) :: (ActionK, [NewK]) where ... Source #

Equations

MkMigrationAction ('OldK _ _ 'True) '[] other = '('RemoveK, other) 
MkMigrationAction ('OldK name comp 'False) ('NewK index name comp 'Nothing 'Nothing ': news) other = '('ActionK 'KeepK index, news ++ other) 
MkMigrationAction ('OldK oldName comp 'False) ('NewK index _ comp ('Just oldName) 'Nothing ': news) other = '('ActionK 'RenameK index, news ++ other) 
MkMigrationAction ('OldK oldName ('Just oldComp) 'False) ('NewK index newName _ rename ('Just oldComp) ': news) other = MkMigrationAction ('OldK oldName ('Just oldComp) 'False) ('NewK index newName ('Just oldComp) rename 'Nothing ': news) other 
MkMigrationAction old (new ': news) other = MkMigrationAction old news (new ': other) 
MkMigrationAction old '[] other = TypeError ("MkMigrationAction:" % (old % other)) 

type family NewMigrationActions (cols :: [NewK]) :: [ActionK] where ... Source #

Equations

NewMigrationActions '[] = '[] 
NewMigrationActions ('NewK index _ _ 'Nothing 'Nothing ': news) = 'ActionK 'AddK index ': NewMigrationActions news 
NewMigrationActions cols = TypeError ("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 ColumnAddition (comp :: Maybe Symbol) (def :: Type) where Source #

Instances

Instances details
ColumnAddition ('Nothing :: Maybe Symbol) () Source # 
Instance details

Defined in Sqel.Migration.Column

PrimColumn a => ColumnAddition ('Nothing :: Maybe Symbol) (MigrationDefault a) Source # 
Instance details

Defined in Sqel.Migration.Column

ColumnAddition ('Just tname) () Source # 
Instance details

Defined in Sqel.Migration.Column

class ColIndex index cols col | index cols -> col where Source #

Methods

colIndex :: NP f cols -> f col Source #

Instances

Instances details
ColIndex (n - 1) cols col => ColIndex (n :: Natural) (c ': cols :: [k]) (col :: k) Source # 
Instance details

Defined in Sqel.Migration.Column

Methods

colIndex :: NP f (c ': cols) -> f col Source #

ColIndex 0 (col ': cols :: [k]) (col :: k) Source # 
Instance details

Defined in Sqel.Migration.Column

Methods

colIndex :: NP f (col ': cols) -> f col Source #

class ReifyModAction action old new where Source #

Instances

Instances details
ReifyModAction 'KeepK old new Source # 
Instance details

Defined in Sqel.Migration.Column

ReifyModAction 'RenameK ('DdlColumnK name compOld modsOld renameOld renameTOld deleteOld typeOld) ('DdlColumnK nameNew compNew modsNew ('Just name) renameTNew delNew typeNew) Source # 
Instance details

Defined in Sqel.Migration.Column

Methods

reifyModAction :: DdlColumn ('DdlColumnK name compOld modsOld renameOld renameTOld deleteOld typeOld) -> DdlColumn ('DdlColumnK nameNew compNew modsNew ('Just name) renameTNew delNew typeNew) -> [ColumnAction] Source #

class ReifyOldAction action old new where Source #

Instances

Instances details
ReifyOldAction 'RemoveK old new Source # 
Instance details

Defined in Sqel.Migration.Column

(ColIndex index news new, ReifyModAction mod old new) => ReifyOldAction ('ActionK mod index) old news Source # 
Instance details

Defined in Sqel.Migration.Column

class ReifyNewAction action new where Source #

Instances

Instances details
(ColIndex index news ('DdlColumnK name comp mods rename renameT delete tpe), OptMod (MigrationDefault tpe) mods def, ColumnAddition comp def) => ReifyNewAction ('ActionK 'AddK index) news Source # 
Instance details

Defined in Sqel.Migration.Column

class ReifyActions actions old new where Source #

Instances

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

Defined in Sqel.Migration.Column

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

Defined in Sqel.Migration.Column

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

Defined in Sqel.Migration.Column

Methods

reifyActions :: NP DdlColumn (o ': old) -> NP DdlColumn new -> [ColumnAction] Source #

class ColumnsChanges old new where Source #

Instances

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

Defined in Sqel.Migration.Column