lorentz-0.4.0: EDSL for the Michelson Language
Safe HaskellNone
LanguageHaskell2010

Lorentz.UStore.Migration.Blocks

Description

Elemental building blocks for migrations.

Synopsis

General

mustoreToOld :: RequireBeInitial touched => (MUStore oldTemplate newTemplate remDiff touched ': s) :-> (UStore oldTemplate ': s) Source #

Get the old version of storage.

This can be applied only in the beginning of migration.

In fact this function is not very useful, all required operations should be available for MUStore, but leaving it here just in case.

class MigrationFinishCheckPosition a where Source #

Methods

migrationFinish :: a Source #

Put this in the end of migration script to get a human-readable message about remaining diff which yet should be covered. Use of this function in migration is fully optional.

This function is not part of mkUStoreMigration for the sake of proper error messages ordering, during development you probably want errors in migration script to be located earlier in code than errors about not fully covered diff (if you used to fix errors in the same order in which they appear).

Instances

Instances details
(i ~ (MUStore oldTempl newTempl diff touched ': s), o ~ (MUStore oldTempl newTempl ('[] :: [DiffItem]) touched ': s), RequireEmptyDiff diff) => MigrationFinishCheckPosition (i :-> o) Source #

This version can be used in mkUStoreMigration.

Instance details

Defined in Lorentz.UStore.Migration.Blocks

Methods

migrationFinish :: i :-> o Source #

(RequireEmptyDiff d1, t1 ~ t2) => MigrationFinishCheckPosition (MigrationBlocks o n d1 t1 ('[] :: [DiffItem]) t2) Source #

This version can be used in mkUStoreMultiMigration as the last migration block.

Instance details

Defined in Lorentz.UStore.Migration.Blocks

Methods

migrationFinish :: MigrationBlocks o n d1 t1 '[] t2 Source #

Elemental steps

migrateCoerceUnsafe :: forall field oldTempl newTempl diff touched newDiff newDiff0 _1 _2 s. ('(_1, newDiff0) ~ CoverDiff 'DcRemove field diff, '(_2, newDiff) ~ CoverDiff 'DcAdd field newDiff0) => Label field -> (MUStore oldTempl newTempl diff touched ': s) :-> (MUStore oldTempl newTempl newDiff touched ': s) Source #

Cast field or submap pretending that its value fits to the new type.

Useful when type of field, e.g. lambda or set of lambdas, is polymorphic over storage type.

migrateGetField :: forall field oldTempl newTempl diff touched fieldTy s. (HasUField field fieldTy oldTempl, RequireUntouched field (field `IsElem` touched)) => Label field -> (MUStore oldTempl newTempl diff touched ': s) :-> (fieldTy ': (MUStore oldTempl newTempl diff touched ': s)) Source #

Get a field present in old version of UStore.

migrateAddField :: forall field oldTempl newTempl diff touched fieldTy newDiff marker s. ('(UStoreFieldExt marker fieldTy, newDiff) ~ CoverDiff 'DcAdd field diff, HasUField field fieldTy newTempl) => Label field -> (fieldTy ': (MUStore oldTempl newTempl diff touched ': s)) :-> (MUStore oldTempl newTempl newDiff (field ': touched) ': s) Source #

Add a field which was not present before. This covers one addition from the diff and any removals of field with given name.

This function cannot overwrite existing field with the same name, if this is necessary use migrateOverwriteField which would declare removal explicitly.

migrateRemoveField :: forall field oldTempl newTempl diff touched fieldTy newDiff marker s. ('(UStoreFieldExt marker fieldTy, newDiff) ~ CoverDiff 'DcRemove field diff, HasUField field fieldTy oldTempl) => Label field -> (MUStore oldTempl newTempl diff touched ': s) :-> (MUStore oldTempl newTempl newDiff (field ': touched) ': s) Source #

Remove a field which should not be present in new version of storage. This covers one removal from the diff.

In fact, this action could be performed automatically, but since removal is a destructive operation, being explicit about it seems like a good thing.

migrateExtractField :: forall field oldTempl newTempl diff touched fieldTy newDiff marker s. ('(UStoreFieldExt marker fieldTy, newDiff) ~ CoverDiff 'DcRemove field diff, HasUField field fieldTy oldTempl, RequireUntouched field (field `IsElem` touched)) => Label field -> (MUStore oldTempl newTempl diff touched ': s) :-> (fieldTy ': (MUStore oldTempl newTempl newDiff (field ': touched) ': s)) Source #

Get and remove a field from old version of UStore.

You probably want to use this more often than plain migrateRemoveField.

migrateOverwriteField :: forall field oldTempl newTempl diff touched fieldTy oldFieldTy marker oldMarker newDiff newDiff0 s. ('(UStoreFieldExt oldMarker oldFieldTy, newDiff0) ~ CoverDiff 'DcRemove field diff, '(UStoreFieldExt marker fieldTy, newDiff) ~ CoverDiff 'DcAdd field newDiff0, HasUField field fieldTy newTempl) => Label field -> (fieldTy ': (MUStore oldTempl newTempl diff touched ': s)) :-> (MUStore oldTempl newTempl newDiff (field ': touched) ': s) Source #

Remove field and write new one in place of it.

This is semantically equivalent to dip (migrateRemoveField label) >> migrateAddField label, but is cheaper.

migrateModifyField :: forall field oldTempl newTempl diff touched fieldTy s. (HasUField field fieldTy oldTempl, HasUField field fieldTy newTempl) => Label field -> (fieldTy ': (MUStore oldTempl newTempl diff touched ': s)) :-> (MUStore oldTempl newTempl diff touched ': s) Source #

Modify field which should stay in new version of storage. This does not affect remaining diff.

Migration batches

muBlock :: ('[MUStore o n d1 t1] :-> '[MUStore o n d2 t2]) -> MigrationBlocks o n d1 t1 d2 t2 Source #

Define a migration atom.

It will be named automatically according to the set of actions it performs (via DMigrationActionDescs). This may be want you want for small sequences of actions, but for complex ones consider using muBlockNamed. Names are used in rendering migration plan.

muBlockNamed :: Text -> ('[MUStore o n d1 t1] :-> '[MUStore o n d2 t2]) -> MigrationBlocks o n d1 t1 d2 t2 Source #

Define a migration atom with given name.

Name will be used when rendering migration plan.

(<-->) :: MigrationBlocks o n d1 t1 d2 t2 -> MigrationBlocks o n d2 t2 d3 t3 -> MigrationBlocks o n d1 t1 d3 t3 infixl 2 Source #

Composition of migration blocks.

($:) :: (a -> b) -> a -> b infixr 7 Source #

This is $ operator with priority higher than <-->.

It allows you writing

mkUStoreBatchedMigration =
  muBlock $: do
    migrateAddField ...
  --
  muBlock $: do
    migrateRemoveField ...

Alternatively, BlockArguments extension can be used.