Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module contains implementation of UStore
.
UStore
is essentially
forall store field type. Lorentz.StoreClass.StoreHasField store field type
modified for the sake of upgradeability.
In API it differs from Store
in the following ways:
1. It keeps both virtual big_map
s and plain fields;
2. Neat conversion between Michelson and Haskell values
is implemented;
3. Regarding composabililty, one can operate with one UStore
and then lift it to a bigger one which includes the former.
This allows for simpler management of stores and clearer error messages.
In spite of this, operations with UStore
s over deeply nested templates will
still work as before.
We represent UStore
as big_map bytes bytes
.
- Plain fields are stored as
key = pack fieldName; value = pack originalValue
. - Virtual
big_map
s are kept askey = pack (bigMapName, originalKey); value = pack originalValue
.
Synopsis
- data UStore (a :: Type)
- newtype k |~> v = UStoreSubMap {
- unUStoreSubMap :: Map k v
- newtype UStoreFieldExt (m :: UStoreMarkerType) (v :: Type) = UStoreField {
- unUStoreField :: v
- type UStoreField = UStoreFieldExt UMarkerPlainField
- type UStoreMarkerType = UStoreMarker -> Type
- class KnownUStoreMarker (marker :: UStoreMarkerType) where
- type ShowUStoreField marker v :: ErrorMessage
- mkFieldMarkerUKey :: MText -> ByteString
- type GetUStoreKey store name = MSKey (GetUStore name store)
- type GetUStoreValue store name = MSValue (GetUStore name store)
- type GetUStoreField store name = FSValue (GetUStore name store)
- type GetUStoreFieldMarker store name = FSMarker (GetUStore name store)
- ustoreMem :: forall store name s. KeyAccessC store name => Label name -> (GetUStoreKey store name ': (UStore store ': s)) :-> (Bool ': s)
- ustoreGet :: forall store name s. (KeyAccessC store name, ValueAccessC store name) => Label name -> (GetUStoreKey store name ': (UStore store ': s)) :-> (Maybe (GetUStoreValue store name) ': s)
- ustoreUpdate :: forall store name s. (KeyAccessC store name, ValueAccessC store name) => Label name -> (GetUStoreKey store name ': (Maybe (GetUStoreValue store name) ': (UStore store ': s))) :-> (UStore store ': s)
- ustoreInsert :: forall store name s. (KeyAccessC store name, ValueAccessC store name) => Label name -> (GetUStoreKey store name ': (GetUStoreValue store name ': (UStore store ': s))) :-> (UStore store ': s)
- ustoreInsertNew :: forall store name s. (KeyAccessC store name, ValueAccessC store name) => Label name -> (forall s0 any. (GetUStoreKey store name ': s0) :-> any) -> (GetUStoreKey store name ': (GetUStoreValue store name ': (UStore store ': s))) :-> (UStore store ': s)
- ustoreDelete :: forall store name s. KeyAccessC store name => Label name -> (GetUStoreKey store name ': (UStore store ': s)) :-> (UStore store ': s)
- ustoreToField :: forall store name s. FieldAccessC store name => Label name -> (UStore store ': s) :-> (GetUStoreField store name ': s)
- ustoreGetField :: forall store name s. FieldAccessC store name => Label name -> (UStore store ': s) :-> (GetUStoreField store name ': (UStore store ': s))
- ustoreSetField :: forall store name s. FieldAccessC store name => Label name -> (GetUStoreField store name ': (UStore store ': s)) :-> (UStore store ': s)
- type HasUStore name key value store = (KeyAccessC store name, ValueAccessC store name, GetUStoreKey store name ~ key, GetUStoreValue store name ~ value)
- type HasUField name ty store = (FieldAccessC store name, GetUStoreField store name ~ ty)
- type HasUStoreForAllIn store constrained = (Generic store, GHasStoreForAllIn constrained (Rep store))
- liftUStore :: (Generic template, RequireAllUniqueFields template) => Label name -> (UStore (GetFieldType template name) ': s) :-> (UStore template ': s)
- unliftUStore :: Generic template => Label name -> (UStore template ': s) :-> (UStore (GetFieldType template name) ': s)
- class Typeable template => UStoreTemplateHasDoc template where
- class KnownUStoreMarker marker => UStoreMarkerHasDoc (marker :: UStoreMarkerType) where
- ustoreMarkerKeyEncoding :: Text -> Text
- mkUStore :: UStoreTraversable MkUStoreTW template => template -> UStore template
- ustoreDecompose :: forall template. UStoreTraversable DecomposeUStoreTW template => UStore template -> Either Text (UStoreContent, template)
- ustoreDecomposeFull :: forall template. UStoreTraversable DecomposeUStoreTW template => UStore template -> Either Text template
- fillUStore :: UStoreTraversable FillUStoreTW template => template -> UStoreMigration () template
- data MkUStoreTW
- data DecomposeUStoreTW
- data FillUStoreTW
- newtype MigrationScript (oldStore :: Type) (newStore :: Type) = MigrationScript {}
- type MigrationScript_ = MigrationScript SomeUTemplate SomeUTemplate
- data UStoreMigration (oldTempl :: Type) (newTempl :: Type)
- migrationToScript :: UStoreMigration os ns -> MigrationScript os ns
- migrationToScriptI :: UStoreMigration os ns -> Identity (MigrationScript os ns)
- migrationToLambda :: UStoreMigration oldTemplate newTemplate -> Lambda (UStore oldTemplate) (UStore newTemplate)
- mkUStoreMigration :: Lambda (MUStore oldTempl newTempl (BuildDiff oldTempl newTempl) '[]) (MUStore oldTempl newTempl '[] _1) -> UStoreMigration oldTempl newTempl
- mustoreToOld :: RequireBeInitial touched => (MUStore oldTemplate newTemplate remDiff touched ': s) :-> (UStore oldTemplate ': s)
- 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))
- 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)
- 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)
- 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))
- 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)
- 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)
- type PickMarkedFields marker template = GPickMarkedFields marker (Rep template)
- type UStoreTraversable way a = (Generic a, GUStoreTraversable way (Rep a), UStoreTraversalWay way)
UStore and related type definitions
data UStore (a :: Type) Source #
Gathers multple fields and BigMap
s under one object.
Type argument of this datatype stands for a "store template" -
a datatype with one constructor and multiple fields, each containing
an object of type UStoreField
or |~>
and corresponding to single
virtual field or BigMap
respectively.
It's also possible to parameterize it with a larger type which is
a product of types satisfying the above property.
Instances
Describes one virtual big map in the storage.
UStoreSubMap | |
|
newtype UStoreFieldExt (m :: UStoreMarkerType) (v :: Type) Source #
Describes plain field in the storage.
UStoreField | |
|
Instances
Eq v => Eq (UStoreFieldExt m v) Source # | |
Defined in Lorentz.UStore.Types (==) :: UStoreFieldExt m v -> UStoreFieldExt m v -> Bool # (/=) :: UStoreFieldExt m v -> UStoreFieldExt m v -> Bool # | |
Show v => Show (UStoreFieldExt m v) Source # | |
Defined in Lorentz.UStore.Types showsPrec :: Int -> UStoreFieldExt m v -> ShowS # show :: UStoreFieldExt m v -> String # showList :: [UStoreFieldExt m v] -> ShowS # | |
Arbitrary v => Arbitrary (UStoreFieldExt m v) Source # | |
Defined in Lorentz.UStore.Types arbitrary :: Gen (UStoreFieldExt m v) # shrink :: UStoreFieldExt m v -> [UStoreFieldExt m v] # |
type UStoreField = UStoreFieldExt UMarkerPlainField Source #
Just a plain field used as data.
type UStoreMarkerType = UStoreMarker -> Type Source #
Specific kind used to designate markers for UStoreFieldExt
.
We suggest that fields may serve different purposes and so annotated with special markers accordingly, which influences translation to Michelson. See example below.
This Haskell kind is implemented like that because we want markers to differ from all
other types in kind; herewith UStoreMarkerType
is still an open kind
(has potentially infinite number of inhabitants).
class KnownUStoreMarker (marker :: UStoreMarkerType) where Source #
Allows to specify format of key under which fields of this type are stored. Useful to avoid collisions.
Nothing
type ShowUStoreField marker v :: ErrorMessage Source #
Display type-level information about UStore field with given marker and field value type. Used for error messages.
mkFieldMarkerUKey :: MText -> ByteString Source #
By field name derive key under which field should be stored.
default mkFieldMarkerUKey :: MText -> ByteString Source #
Instances
KnownUStoreMarker UMarkerPlainField Source # | |
Defined in Lorentz.UStore.Types type ShowUStoreField UMarkerPlainField v :: ErrorMessage Source # mkFieldMarkerUKey :: MText -> ByteString Source # |
Type-lookup-by-name
type GetUStoreKey store name = MSKey (GetUStore name store) Source #
Get type of submap key.
type GetUStoreValue store name = MSValue (GetUStore name store) Source #
Get type of submap value.
type GetUStoreField store name = FSValue (GetUStore name store) Source #
Get type of plain field. This ignores marker with field type.
type GetUStoreFieldMarker store name = FSMarker (GetUStore name store) Source #
Get kind of field.
Instructions
ustoreMem :: forall store name s. KeyAccessC store name => Label name -> (GetUStoreKey store name ': (UStore store ': s)) :-> (Bool ': s) Source #
ustoreGet :: forall store name s. (KeyAccessC store name, ValueAccessC store name) => Label name -> (GetUStoreKey store name ': (UStore store ': s)) :-> (Maybe (GetUStoreValue store name) ': s) Source #
ustoreUpdate :: forall store name s. (KeyAccessC store name, ValueAccessC store name) => Label name -> (GetUStoreKey store name ': (Maybe (GetUStoreValue store name) ': (UStore store ': s))) :-> (UStore store ': s) Source #
ustoreInsert :: forall store name s. (KeyAccessC store name, ValueAccessC store name) => Label name -> (GetUStoreKey store name ': (GetUStoreValue store name ': (UStore store ': s))) :-> (UStore store ': s) Source #
ustoreInsertNew :: forall store name s. (KeyAccessC store name, ValueAccessC store name) => Label name -> (forall s0 any. (GetUStoreKey store name ': s0) :-> any) -> (GetUStoreKey store name ': (GetUStoreValue store name ': (UStore store ': s))) :-> (UStore store ': s) Source #
Insert a key-value pair, but fail if it will overwrite some existing entry.
ustoreDelete :: forall store name s. KeyAccessC store name => Label name -> (GetUStoreKey store name ': (UStore store ': s)) :-> (UStore store ': s) Source #
ustoreToField :: forall store name s. FieldAccessC store name => Label name -> (UStore store ': s) :-> (GetUStoreField store name ': s) Source #
ustoreGetField :: forall store name s. FieldAccessC store name => Label name -> (UStore store ': s) :-> (GetUStoreField store name ': (UStore store ': s)) Source #
ustoreSetField :: forall store name s. FieldAccessC store name => Label name -> (GetUStoreField store name ': (UStore store ': s)) :-> (UStore store ': s) Source #
Like setField
, but for UStore
.
Instruction constraints
type HasUStore name key value store = (KeyAccessC store name, ValueAccessC store name, GetUStoreKey store name ~ key, GetUStoreValue store name ~ value) Source #
This constraint can be used if a function needs to work with big store, but needs to know only about some submap(s) of it.
It can use all UStore operations for a particular name, key and value without knowing whole template.
type HasUField name ty store = (FieldAccessC store name, GetUStoreField store name ~ ty) Source #
This constraint can be used if a function needs to work with big store, but needs to know only about some field of it.
type HasUStoreForAllIn store constrained = (Generic store, GHasStoreForAllIn constrained (Rep store)) Source #
Write down all sensisble constraints which given store
satisfies
and apply them to constrained
.
This store should have |~>
and UStoreField
fields in its immediate fields,
no deep inspection is performed.
UStore composability
liftUStore :: (Generic template, RequireAllUniqueFields template) => Label name -> (UStore (GetFieldType template name) ': s) :-> (UStore template ': s) Source #
Lift an UStore
to another UStore
which contains all the entries
of the former under given field.
This function is not intended for use in migrations, only in normal entry points.
Note that this function ensures that template of resulting store
does not contain inner nested templates with duplicated fields,
otherwise UStore
invariants could get broken.
unliftUStore :: Generic template => Label name -> (UStore template ': s) :-> (UStore (GetFieldType template name) ': s) Source #
Unlift an UStore
to a smaller UStore
which is part of the former.
This function is not intended for use in migrations, only in normal entry points.
Surprisingly, despite smaller UStore
may have extra entries,
this function is safe when used in contract code.
Truly, all getters and setters are still safe to use.
Also, there is no way for the resulting small UStore
to leak outside
of the contract since the only place where big_map
can appear
is contract storage, so this small UStore
can be either dropped
or lifted back via liftUStore
to appear as part of the new contract's state.
When this function is run as part of standalone instructions sequence,
not as part of contract code (e.g. in tests), you may get an UStore
with entries not inherent to it.
Documentation
class Typeable template => UStoreTemplateHasDoc template where Source #
Information for UStore template required for documentation.
You only need to instantiate this for templates used directly in UStore, nested subtemplates do not need this instance.
ustoreTemplateDocName :: Text Source #
UStore template name as it appears in documentation.
Should be only 1 word.
default ustoreTemplateDocName :: (Generic template, KnownSymbol (GenericTypeName template)) => Text Source #
ustoreTemplateDocDescription :: Markdown Source #
Description of template.
ustoreTemplateDocContents :: Markdown Source #
Description of template entries.
default ustoreTemplateDocContents :: UStoreTraversable DocumentTW template => Markdown Source #
ustoreTemplateDocDependencies :: [SomeTypeWithDoc] Source #
default ustoreTemplateDocDependencies :: UStoreTraversable DocumentTW template => [SomeTypeWithDoc] Source #
Instances
class KnownUStoreMarker marker => UStoreMarkerHasDoc (marker :: UStoreMarkerType) where Source #
Instantiated for documented UStore markers.
ustoreMarkerKeyEncoding :: Text -> Text Source #
Specifies key encoding.
You accept description of field name, and should return how is it encoded
as key of big_map bytes bytes
.
Instances
UStoreMarkerHasDoc UMarkerPlainField Source # | |
Defined in Lorentz.UStore.Doc ustoreMarkerKeyEncoding :: Text -> Text Source # |
UStore management from Haskell
mkUStore :: UStoreTraversable MkUStoreTW template => template -> UStore template Source #
Make UStore
from separate big_map
s and fields.
ustoreDecompose :: forall template. UStoreTraversable DecomposeUStoreTW template => UStore template -> Either Text (UStoreContent, template) Source #
Decompose UStore
into separate big_map
s and fields.
Since this function needs to UNPACK
content of UStore
to actual
keys and values, you have to provide UnpackEnv
.
Along with resulting value, you get a list of UStore
entries which
were not recognized as belonging to any submap or field according to
UStore
's template - this should be empty unless UStore
invariants
were violated.
ustoreDecomposeFull :: forall template. UStoreTraversable DecomposeUStoreTW template => UStore template -> Either Text template Source #
Like ustoreDecompose
, but requires all entries from UStore
to be
recognized.
fillUStore :: UStoreTraversable FillUStoreTW template => template -> UStoreMigration () template Source #
Make migration script which initializes UStore
from scratch.
data MkUStoreTW Source #
Declares handlers for UStore creation from template.
Instances
data DecomposeUStoreTW Source #
Declares handlers for UStore conversion to template.
Instances
data FillUStoreTW Source #
Declares handlers for UStore filling via lambda.
Instances
Migrations
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
data UStoreMigration (oldTempl :: Type) (newTempl :: Type) Source #
Keeps information about migration between UStore
s with two given
templates.
Instances
MapLorentzInstr (UStoreMigration os ns) Source # | |
Defined in Lorentz.UStore.Migration.Base mapLorentzInstr :: (forall (i :: [Type]) (o :: [Type]). (i :-> o) -> i :-> o) -> UStoreMigration os ns -> UStoreMigration os ns Source # |
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.
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.
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
.
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.
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.
Extras
type PickMarkedFields marker template = GPickMarkedFields marker (Rep template) Source #
Collect all fields with the given marker.
type UStoreTraversable way a = (Generic a, GUStoreTraversable way (Rep a), UStoreTraversalWay way) Source #
Constraint for UStore traversal.