lorentz-0.1.0: EDSL for the Michelson Language

Safe HaskellNone
LanguageHaskell2010

Lorentz.UStore.Migration.Base

Contents

Description

Basic migration primitives.

All primitives in one scheme:

MigrationBlocks (batched migrations writing) /| || muBlock // || mkUStoreBatchedMigration // || // || MUStore || UStore template value (simple migration writing) || (storage initialization) \ || // \ || // mkUStoreMigration \ || // fillUStore | / |/ UStoreMigration (whole migration) || \ || \ migrationToScript || \ compileMigration || \ MigrationBatching || \ (way to slice migration) || \ // || \ // || | |/ || UStoreMigrationCompiled || (sliced migration) || // \ || migrationToScripts \ buildMigrationPlan || // \ migrationStagesNum || // \ ... / |/ | MigrationScript Information about migration (part of migration which (migration plan, stages number...) fits into Tezos transaction)

Synopsis

UStore utilities

data SomeUTemplate Source #

Dummy template for UStore, use this when you want to forget exact template and make type of store homomorphic.

type UStore_ = UStore SomeUTemplate Source #

UStore with hidden template.

Basic migration primitives

newtype MigrationScript (oldStore :: Type) (newStore :: Type) Source #

Code of migration for UStore.

Invariant: preferably should fit into op size / gas limits (quite obvious). Often this stands for exactly one stage of migration (one Tezos transaction).

Instances
CanCastTo (Lambda (UStore ot1) (UStore nt1)) (Lambda (UStore ot2) (UStore nt2)) => CanCastTo (MigrationScript ot1 nt1 :: Type) (MigrationScript ot2 nt2 :: Type) Source # 
Instance details

Defined in Lorentz.UStore.Migration.Base

Methods

castDummy :: () Source #

Show (MigrationScript oldStore newStore) Source # 
Instance details

Defined in Lorentz.UStore.Migration.Base

Methods

showsPrec :: Int -> MigrationScript oldStore newStore -> ShowS #

show :: MigrationScript oldStore newStore -> String #

showList :: [MigrationScript oldStore newStore] -> ShowS #

Generic (MigrationScript oldStore newStore) Source # 
Instance details

Defined in Lorentz.UStore.Migration.Base

Associated Types

type Rep (MigrationScript oldStore newStore) :: Type -> Type #

Methods

from :: MigrationScript oldStore newStore -> Rep (MigrationScript oldStore newStore) x #

to :: Rep (MigrationScript oldStore newStore) x -> MigrationScript oldStore newStore #

Wrapped (MigrationScript oldStore newStore) Source # 
Instance details

Defined in Lorentz.UStore.Migration.Base

Associated Types

type Unwrapped (MigrationScript oldStore newStore) :: Type #

Methods

_Wrapped' :: Iso' (MigrationScript oldStore newStore) (Unwrapped (MigrationScript oldStore newStore)) #

(Typeable oldStore, Typeable newStore) => TypeHasDoc (MigrationScript oldStore newStore) Source # 
Instance details

Defined in Lorentz.UStore.Migration.Base

IsoValue (MigrationScript oldStore newStore) Source # 
Instance details

Defined in Lorentz.UStore.Migration.Base

Associated Types

type ToT (MigrationScript oldStore newStore) :: T #

Methods

toVal :: MigrationScript oldStore newStore -> Value (ToT (MigrationScript oldStore newStore)) #

fromVal :: Value (ToT (MigrationScript oldStore newStore)) -> MigrationScript oldStore newStore #

type Rep (MigrationScript oldStore newStore) Source # 
Instance details

Defined in Lorentz.UStore.Migration.Base

type Rep (MigrationScript oldStore newStore) = D1 (MetaData "MigrationScript" "Lorentz.UStore.Migration.Base" "lorentz-0.1.0-1IijY81BuYC4to9wXiBP3G" True) (C1 (MetaCons "MigrationScript" PrefixI True) (S1 (MetaSel (Just "unMigrationScript") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Lambda UStore_ UStore_))))
type Unwrapped (MigrationScript oldStore newStore) Source # 
Instance details

Defined in Lorentz.UStore.Migration.Base

type Unwrapped (MigrationScript oldStore newStore) = GUnwrapped (Rep (MigrationScript oldStore newStore))
type ToT (MigrationScript oldStore newStore) Source # 
Instance details

Defined in Lorentz.UStore.Migration.Base

type ToT (MigrationScript oldStore newStore) = GValueType (Rep (MigrationScript oldStore newStore))

type MigrationScriptFrom oldStore = MigrationScript oldStore SomeUTemplate Source #

Corner case of MigrationScript with some type argument unknown.

You can turn this into MigrationScript using checkedCoerce.

data MigrationAtom Source #

Minimal possible piece of migration script.

Different atoms can be arbitrarily reordered and separated across migration stages, but each single atom is treated as a whole.

Splitting migration into atoms is responsibility of migration writer.

data UStoreMigration (oldTempl :: Type) (newTempl :: Type) where Source #

Keeps information about migration between UStores with two given templates.

Constructors

UStoreMigration :: [MigrationAtom] -> UStoreMigration oldTempl newTempl 

newtype MigrationBlocks (oldTemplate :: Type) (newTemplate :: Type) (preRemDiff :: [DiffItem]) (preTouched :: [Symbol]) (postRemDiff :: [DiffItem]) (postTouched :: [Symbol]) Source #

A bunch of migration atoms produced by migration writer.

Instances
(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 #

newtype MUStore (oldTemplate :: Type) (newTemplate :: Type) (remDiff :: [DiffItem]) (touched :: [Symbol]) Source #

Wrapper over UStore which is currently being migrated.

In type-level arguments it keeps

  • Old and new UStore templates - mostly for convenience of the implementation.
  • Remaining diff which yet should be covered. Here we track migration progress. Once remaining diff is empty, migration is finished.
  • Names of fields which have already been touched by migration. Required to make getters safe.

Constructors

MUStoreUnsafe (UStore oldTemplate) 
Instances
Generic (MUStore oldTemplate newTemplate remDiff touched) Source # 
Instance details

Defined in Lorentz.UStore.Migration.Base

Associated Types

type Rep (MUStore oldTemplate newTemplate remDiff touched) :: Type -> Type #

Methods

from :: MUStore oldTemplate newTemplate remDiff touched -> Rep (MUStore oldTemplate newTemplate remDiff touched) x #

to :: Rep (MUStore oldTemplate newTemplate remDiff touched) x -> MUStore oldTemplate newTemplate remDiff touched #

IsoValue (MUStore oldTemplate newTemplate remDiff touched) Source # 
Instance details

Defined in Lorentz.UStore.Migration.Base

Associated Types

type ToT (MUStore oldTemplate newTemplate remDiff touched) :: T #

Methods

toVal :: MUStore oldTemplate newTemplate remDiff touched -> Value (ToT (MUStore oldTemplate newTemplate remDiff touched)) #

fromVal :: Value (ToT (MUStore oldTemplate newTemplate remDiff touched)) -> MUStore oldTemplate newTemplate remDiff touched #

type Rep (MUStore oldTemplate newTemplate remDiff touched) Source # 
Instance details

Defined in Lorentz.UStore.Migration.Base

type Rep (MUStore oldTemplate newTemplate remDiff touched) = D1 (MetaData "MUStore" "Lorentz.UStore.Migration.Base" "lorentz-0.1.0-1IijY81BuYC4to9wXiBP3G" True) (C1 (MetaCons "MUStoreUnsafe" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (UStore oldTemplate))))
type ToT (MUStore oldTemplate newTemplate remDiff touched) Source # 
Instance details

Defined in Lorentz.UStore.Migration.Base

type ToT (MUStore oldTemplate newTemplate remDiff touched) = GValueType (Rep (MUStore oldTemplate newTemplate remDiff touched))

migrationToLambda :: UStoreMigration oldTemplate newTemplate -> Lambda (UStore oldTemplate) (UStore newTemplate) Source #

Turn Migration into a whole piece of code for transforming storage.

This is not want you'd want to use for contract deployment because of gas and operation size limits that Tezos applies to transactions.

mapMigrationCode :: (forall i o. (i :-> o) -> i :-> o) -> UStoreMigration os ns -> UStoreMigration os ns Source #

Modify all code in migration.

Simple migrations

mkUStoreMigration :: Lambda (MUStore oldTempl newTempl (BuildDiff oldTempl newTempl) '[]) (MUStore oldTempl newTempl '[] _1) -> UStoreMigration oldTempl newTempl Source #

Safe way to create migration scripts for UStore.

You have to supply a code which would transform MUStore, coverring required diff step-by-step. All basic instructions work, also use migrate* functions from this module to operate with MUStore.

This method produces a whole migration, it cannot be splitted in batches. In case if your migration is too big to be applied within a single transaction, use mkUStoreBatchedMigration.

migrationToScript :: UStoreMigration os ns -> MigrationScript os ns Source #

Get migration script in case of simple (non-batched) migration.

migrationToScriptI :: UStoreMigration os ns -> Identity (MigrationScript os ns) Source #

Get migration script in case of simple (non-batched) migration.

Batched migrations

data MigrationBatching (structure :: Type -> Type) (batchInfo :: Type) Source #

Way of distributing migration atoms among batches.

This also participates in describing migration plan and should contain information which would clarify to a user why migration is splitted such a way. Objects of type batchInfo stand for information corresponding to a batch and may include e.g. names of taken actions and gas consumption.

Type argument structure stands for container where batches will be put to and is usually a list ('[]').

When writing an instance of this datatype, you should tend to produce as few batches as possible because Tezos transaction execution overhead is quite high; though these batches should still preferably fit into gas limit.

Note that we never fail here because reaching perfect consistency with Tezos gas model is beyond dreams for now, even if our model predicts that some migration atom cannot be fit into gas limit, Tezos node can think differently and accept the migration. If your batching function can make predictions about fitting into gas limit, consider including this information in batchInfo type.

See batching implementations in Lorentz.UStore.Migration.Batching module.

Constructors

MigrationBatching ([MigrationAtom] -> structure (batchInfo, MigrationScript_)) 

mbBatchesAsIs :: MigrationBatching [] Text Source #

Put each migration atom to a separate batch.

In most cases this is not what you want, but may be useful if e.g. you write your migration manually.

mbNoBatching :: MigrationBatching Identity Text Source #

Put the whole migration into one batch.

compileMigration :: Functor t => MigrationBatching t batchInfo -> UStoreMigration ot nt -> UStoreMigrationCompiled ot nt t batchInfo Source #

Compile migration for use in production.

newtype UStoreMigrationCompiled (oldStore :: Type) (newStore :: Type) (structure :: Type -> Type) (batchInfo :: Type) Source #

Migration script splitted in batches.

This is an intermediate form of migration content and needed because compiling UStoreMigration is a potentially heavyweight operation, and after compilation is performed you may need to get various information like number of migration steps, migration script, migration plan and other.

Constructors

UStoreMigrationCompiled 

Fields

mkUStoreBatchedMigration :: MigrationBlocks oldTempl newTempl (BuildDiff oldTempl newTempl) '[] '[] _1 -> UStoreMigration oldTempl newTempl Source #

Version of mkUStoreMigration which allows splitting migration in batches.

Here you supply a sequence of migration blocks which then are automatically distributed among migration stages.

migrationToScripts :: Traversable t => UStoreMigrationCompiled os ns t batchInfo -> t (MigrationScript os ns) Source #

Get migration scripts, each to be executed in separate Tezos transaction.

migrationToScriptsList :: Traversable t => UStoreMigrationCompiled os ns t batchInfo -> [MigrationScript os ns] Source #

Get migration scripts as list.

migrationToInfo :: Traversable t => UStoreMigrationCompiled ot nt t batchInfo -> t batchInfo Source #

Get information about each batch.

migrationStagesNum :: Traversable t => UStoreMigrationCompiled ot nt t batchInfo -> Int Source #

Number of stages in migration.

buildMigrationPlan :: (Traversable t, Buildable batchInfo) => UStoreMigrationCompiled ot nt t batchInfo -> Builder Source #

Render migration plan.

Manual migrations

manualWithOldUStore :: ('[UStore oldStore] :-> '[UStore oldStore]) -> MigrationScript oldStore newStore Source #

manualWithNewUStore :: ('[UStore newStore] :-> '[UStore newStore]) -> MigrationScript oldStore newStore Source #

manualConcatMigrationScripts :: [MigrationScript os ns] -> MigrationScript os ns Source #

Merge several migration scripts. Used in manual migrations.

This function is generally unsafe because resulting migration script can fail to fit into operation size limit.

manualMapMigrationScript :: (('[UStore_] :-> '[UStore_]) -> '[UStore_] :-> '[UStore_]) -> MigrationScript oldStore newStore -> MigrationScript oldStore newStore Source #

Extras

data DMigrationActionType Source #

An action on storage entry.

Constructors

DAddAction Text

Some sort of addition: "init", "set", "overwrite", e.t.c.

DDelAction

Removal.

data DMigrationActionDesc Source #

Describes single migration action.

In most cases it is possible to derive reasonable description for migration atom automatically, this datatype exactly carries this information.

Constructors

DMigrationActionDesc 

Fields

attachMigrationActionName :: (KnownSymbol fieldName, SingI (ToT fieldTy)) => DMigrationActionType -> Label fieldName -> Proxy fieldTy -> s :-> s Source #

Add description of action, it will be used in rendering migration plan and some batching implementations.

Internals

formMigrationAtom :: Maybe Text -> Lambda UStore_ UStore_ -> MigrationAtom Source #

Create migration atom from code.

This is an internal function, should not be used for writing migrations.

Orphan instances

SameUStoreTemplate template1 template2 => CanCastTo (UStore template1 :: Type) (UStore template2 :: Type) Source #

We allow casting between UStore_ and UStore freely.

Instance details

Methods

castDummy :: () Source #