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

Lorentz.StoreClass

Description

This module provides storage interfaces.

Synopsis

Class

class StoreHasField store fname ftype | store fname -> ftype where Source #

Provides operations on fields for storage.

Methods

storeFieldOps :: StoreFieldOps store fname ftype Source #

Instances

Instances details
HasUField fname ftype templ => StoreHasField (UStore templ) fname ftype Source # 
Instance details

Defined in Lorentz.UStore.Instances

Methods

storeFieldOps :: StoreFieldOps (UStore templ) fname ftype Source #

(StoreHasField other fname ftype, IsoValue store, IsoValue other) => StoreHasField (StorageSkeleton store other) fname ftype Source # 
Instance details

Defined in Lorentz.Store

Methods

storeFieldOps :: StoreFieldOps (StorageSkeleton store other) fname ftype Source #

data StoreFieldOps store fname ftype Source #

Datatype containing the full implementation of StoreHasField typeclass.

We use this grouping because in most cases the implementation will be chosen among the default ones, and initializing all methods at once is simpler and more consistent. (One can say that we are trying to emulate the DerivingVia extension.)

Constructors

StoreFieldOps 

Fields

class StoreHasSubmap store mname key value | store mname -> key value where Source #

Provides operations on submaps of storage.

Methods

storeSubmapOps :: StoreSubmapOps store mname key value Source #

Instances

Instances details
HasUStore mname key value templ => StoreHasSubmap (UStore templ) mname key value Source # 
Instance details

Defined in Lorentz.UStore.Instances

Methods

storeSubmapOps :: StoreSubmapOps (UStore templ) mname key value Source #

(StoreMemC store name, StoreGetC store name, StoreUpdateC store name, key ~ GetStoreKey store name, value ~ GetStoreValue store name) => StoreHasSubmap (Store store) name key value Source # 
Instance details

Defined in Lorentz.Store

Methods

storeSubmapOps :: StoreSubmapOps (Store store) name key value Source #

(key ~ key', value ~ value', NiceComparable key) => StoreHasSubmap (Map key' value') name key value Source #

Map can be used as standalone key-value storage if very needed.

Instance details

Defined in Lorentz.StoreClass

Methods

storeSubmapOps :: StoreSubmapOps (Map key' value') name key value Source #

(key ~ key', value ~ value', NiceComparable key) => StoreHasSubmap (BigMap key' value') name key value Source #

BigMap can be used as standalone key-value storage, name of submap is not accounted in this case.

Instance details

Defined in Lorentz.StoreClass

Methods

storeSubmapOps :: StoreSubmapOps (BigMap key' value') name key value Source #

(StoreMemC store name, StoreGetC store name, StoreUpdateC store name, key ~ GetStoreKey store name, value ~ GetStoreValue store name, IsoValue other) => StoreHasSubmap (StorageSkeleton store other) name key value Source # 
Instance details

Defined in Lorentz.Store

Methods

storeSubmapOps :: StoreSubmapOps (StorageSkeleton store other) name key value Source #

data StoreSubmapOps store mname key value Source #

Datatype containing the full implementation of StoreHasSubmap typeclass.

We use this grouping because in most cases the implementation will be chosen among the default ones, and initializing all methods at once is simpler and more consistent. (One can say that we are trying to emulate the DerivingVia extension.)

Constructors

StoreSubmapOps 

Fields

class StoreHasEntrypoint store epName epParam epStore | store epName -> epParam epStore where Source #

Provides operations on stored entrypoints.

store is the storage containing both the entrypoint epName (note: it has to be in a BigMap to take advantage of lazy evaluation) and the epStore field this operates on.

Methods

storeEpOps :: StoreEntrypointOps store epName epParam epStore Source #

data StoreEntrypointOps store epName epParam epStore Source #

Datatype containing the full implementation of StoreHasEntrypoint typeclass.

We use this grouping because in most cases the implementation will be chosen among the default ones, and initializing all methods at once is simpler and more consistent. (One can say that we are trying to emulate the DerivingVia extension.)

Constructors

StoreEntrypointOps 

Fields

Useful type synonyms

type EntrypointLambda param store = Lambda (param, store) ([Operation], store) Source #

Type synonym for a Lambda that can be used as an entrypoint

type EntrypointsField param store = BigMap MText (EntrypointLambda param store) Source #

Type synonym of a BigMap mapping MText (entrypoint names) to EntrypointLambda.

This is useful when defining instances of StoreHasEntrypoint as a storage field containing one or more entrypoints (lambdas) of the same type.

Expressing constraints on storage

data k ~> v infix 9 Source #

Indicates a submap with given key and value types.

data param ::-> store infix 9 Source #

Indicates a stored entrypoint with the given param and store types.

type family StorageContains store (content :: [NamedField]) :: Constraint where ... Source #

Concise way to write down constraints with expected content of a storage.

Use it like follows:

type StorageConstraint store = StorageContains store
  [ "fieldInt" := Int
  , "fieldNat" := Nat
  , "epsToNat" := Int ::-> Nat
  , "balances" := Address ~> Int
  ]

Equations

StorageContains _ '[] = () 
StorageContains store ((n := (k ~> v)) ': ct) = (StoreHasSubmap store n k v, StorageContains store ct) 
StorageContains store ((n := (ep ::-> es)) ': ct) = (StoreHasEntrypoint store n ep es, StorageContains store ct) 
StorageContains store ((n := ty) ': ct) = (StoreHasField store n ty, StorageContains store ct) 

Methods to work with storage

stToField :: StoreHasField store fname ftype => Label fname -> (store ': s) :-> (ftype ': s) Source #

Pick storage field.

stGetField :: StoreHasField store fname ftype => Label fname -> (store ': s) :-> (ftype ': (store ': s)) Source #

Get storage field, preserving the storage itself on stack.

stSetField :: StoreHasField store fname ftype => Label fname -> (ftype ': (store ': s)) :-> (store ': s) Source #

Update storage field.

stMem :: StoreHasSubmap store mname key value => Label mname -> (key ': (store ': s)) :-> (Bool ': s) Source #

Check value presence in storage.

stGet :: (StoreHasSubmap store mname key value, KnownValue value) => Label mname -> (key ': (store ': s)) :-> (Maybe value ': s) Source #

Get value in storage.

stUpdate :: StoreHasSubmap store mname key value => Label mname -> (key ': (Maybe value ': (store ': s))) :-> (store ': s) Source #

Update a value in storage.

stDelete :: forall store mname key value s. (StoreHasSubmap store mname key value, KnownValue value) => Label mname -> (key ': (store ': s)) :-> (store ': s) Source #

Delete a value in storage.

stInsert :: StoreHasSubmap store mname key value => Label mname -> (key ': (value ': (store ': s))) :-> (store ': s) Source #

Add a value in storage.

stInsertNew :: StoreHasSubmap store mname key value => Label mname -> (forall s0 any. (key ': s0) :-> any) -> (key ': (value ': (store ': s))) :-> (store ': s) Source #

Add a value in storage, but fail if it will overwrite some existing entry.

stEntrypoint :: StoreHasEntrypoint store epName epParam epStore => Label epName -> (epParam ': (store ': s)) :-> (([Operation], store) ': s) Source #

Extracts and executes the epName entrypoint lambda from storage, returing the updated full storage (store) and the produced Operations.

stToEpLambda :: StoreHasEntrypoint store epName epParam epStore => Label epName -> (store ': s) :-> (EntrypointLambda epParam epStore ': s) Source #

Pick stored entrypoint lambda.

stGetEpLambda :: StoreHasEntrypoint store epName epParam epStore => Label epName -> (store ': s) :-> (EntrypointLambda epParam epStore ': (store ': s)) Source #

Get stored entrypoint lambda, preserving the storage itself on the stack.

stSetEpLambda :: StoreHasEntrypoint store epName epParam epStore => Label epName -> (EntrypointLambda epParam epStore ': (store ': s)) :-> (store ': s) Source #

Stores the entrypoint lambda in the storage. Fails if already set.

stToEpStore :: StoreHasEntrypoint store epName epParam epStore => Label epName -> (store ': s) :-> (epStore ': s) Source #

Pick the sub-storage that the entrypoint operates on.

stGetEpStore :: StoreHasEntrypoint store epName epParam epStore => Label epName -> (store ': s) :-> (epStore ': (store ': s)) Source #

Get the sub-storage that the entrypoint operates on, preserving the storage itself on the stack.

stSetEpStore :: StoreHasEntrypoint store epName epParam epStore => Label epName -> (epStore ': (store ': s)) :-> (store ': s) Source #

Update the sub-storage that the entrypoint operates on.

Implementations

storeFieldOpsADT :: HasFieldOfType dt fname ftype => StoreFieldOps dt fname ftype Source #

Implementation of StoreHasField for case of datatype keeping a pack of fields.

storeEntrypointOpsADT :: (HasFieldOfType store epmName (EntrypointsField epParam epStore), HasFieldOfType store epsName epStore, KnownValue epParam, KnownValue epStore) => Label epmName -> Label epsName -> StoreEntrypointOps store epName epParam epStore Source #

Implementation of StoreHasEntrypoint for a datatype keeping a pack of fields, among which one has contains the entrypoint and another is what such entrypoint operates on.

storeEntrypointOpsFields :: (StoreHasField store epmName (EntrypointsField epParam epStore), StoreHasField store epsName epStore, KnownValue epParam, KnownValue epStore) => Label epmName -> Label epsName -> StoreEntrypointOps store epName epParam epStore Source #

Implementation of StoreHasEntrypoint for a datatype that has a StoreHasField for an EntrypointsField that contains the entrypoint and a StoreHasField for the field such entrypoint operates on.

storeEntrypointOpsSubmapField :: (StoreHasSubmap store epmName MText (EntrypointLambda epParam epStore), StoreHasField store epsName epStore, KnownValue epParam, KnownValue epStore) => Label epmName -> Label epsName -> StoreEntrypointOps store epName epParam epStore Source #

Implementation of StoreHasEntrypoint for a datatype that has a StoreHasSubmap that contains the entrypoint and a StoreHasField for the field such entrypoint operates on.

storeFieldOpsDeeper :: (HasFieldOfType storage fieldsPartName fields, StoreHasField fields fname ftype) => Label fieldsPartName -> StoreFieldOps storage fname ftype Source #

Implementation of StoreHasField for a data type which has an instance of StoreHasField inside. For instance, it can be used for top-level storage.

storeSubmapOpsDeeper :: (HasFieldOfType storage bigMapPartName fields, StoreHasSubmap fields mname key value) => Label bigMapPartName -> StoreSubmapOps storage mname key value Source #

Implementation of StoreHasSubmap for a data type which has an instance of StoreHasSubmap inside. For instance, it can be used for top-level storage.

storeEntrypointOpsDeeper :: (HasFieldOfType store nameInStore substore, StoreHasEntrypoint substore epName epParam epStore) => Label nameInStore -> StoreEntrypointOps store epName epParam epStore Source #

Implementation of StoreHasEntrypoint for a data type which has an instance of StoreHasEntrypoint inside. For instance, it can be used for top-level storage.

storeFieldOpsReferTo :: Label name -> StoreFieldOps storage name field -> StoreFieldOps storage desiredName field Source #

Pretend that given StoreFieldOps implementation is made up for field with name desiredName, not its actual name. Logic of the implementation remains the same.

See also storeSubmapOpsReferTo.

storeSubmapOpsReferTo :: Label name -> StoreSubmapOps storage name key value -> StoreSubmapOps storage desiredName key value Source #

Pretend that given StoreSubmapOps implementation is made up for submap with name desiredName, not its actual name. Logic of the implementation remains the same.

Use case: imagine that your code requires access to submap named X, but in your storage that submap is called Y. Then you implement the instance which makes X refer to Y:

instance StoreHasSubmap Store X Key Value where
  storeSubmapOps = storeSubmapOpsReferTo #Y storeSubmapOpsForY

storeEntrypointOpsReferTo :: Label epName -> StoreEntrypointOps store epName epParam epStore -> StoreEntrypointOps store desiredName epParam epStore Source #

Pretend that given StoreEntrypointOps implementation is made up for entrypoint with name desiredName, not its actual name. Logic of the implementation remains the same.

See also storeSubmapOpsReferTo.

composeStoreFieldOps :: Label nameInStore -> StoreFieldOps store nameInStore substore -> StoreFieldOps substore nameInSubstore field -> StoreFieldOps store nameInSubstore field Source #

Chain two implementations of field operations.

Suits for a case when your store does not contain its fields directly rather has a nested structure.

composeStoreSubmapOps :: Label nameInStore -> StoreFieldOps store nameInStore substore -> StoreSubmapOps substore mname key value -> StoreSubmapOps store mname key value Source #

Chain implementations of field and submap operations.

composeStoreEntrypointOps :: Label nameInStore -> StoreFieldOps store nameInStore substore -> StoreEntrypointOps substore epName epParam epStore -> StoreEntrypointOps store epName epParam epStore Source #

Storage generation

mkStoreEp :: Label epName -> EntrypointLambda epParam epStore -> EntrypointsField epParam epStore Source #

Utility to create EntrypointsFields from an entrypoint name (epName) and an EntrypointLambda implementation. Note that you need to merge multiple of these (with <>) if your field contains more than one entrypoint lambda.