morley-upgradeable-0.3: Upgradeability infrastructure based on Morley.
Safe HaskellNone
LanguageHaskell2010

Lorentz.Contracts.Upgradeable.StorageDriven

Description

Contracts based on storage-driven upgrages.

Here entrypoints are declared as part of UStore template, then we automatically derive public API of the contract from it.

Migration mechanism for storage (see Migration) also applies to these entrypoints.

This approach differs from one in Lorentz.Contracts.Upgradeable.EntrypointWise in the following points: 1. Storage migrations are not handled here, only UContractRouter creation. The former is comprehensively handled by Migration. 2. Contract interface is declared via storage - UStoreEntrypoint entries in storage define which public entrypoints (those which are callable via passing UParam) the contract will have. 3. Parameter dispatch fallback is made part of UContractRouter, not storing it in storage here for simplicity. The user can still decide to keep fallback implementation in storage if it is big and then refer to it in SduFallback.

Synopsis

Documentation

type UStoreEntrypoint store arg = UStoreFieldExt UMarkerEntrypoint (SduEntrypoint store arg) Source #

Public entrypoint of a contract kept in UStore.

These are mere UStore fields but treated specially by mkSduContract function which produces UContractRouter capable of calling these entrypoints.

This type is not intended for keeping internal code, in such case consider using UStoreField instead.

data UMarkerEntrypoint :: UStoreMarkerType Source #

Instances

Instances details
KnownUStoreMarker UMarkerEntrypoint Source # 
Instance details

Defined in Lorentz.Contracts.Upgradeable.StorageDriven

UStoreMarkerHasDoc UMarkerEntrypoint Source # 
Instance details

Defined in Lorentz.Contracts.Upgradeable.StorageDriven

(TypeHasDoc arg, NiceParameterFull arg) => UStoreTraversalFieldHandler SduAddEntrypointDocTW UMarkerEntrypoint (SduEntrypoint store arg) Source # 
Instance details

Defined in Lorentz.Contracts.Upgradeable.StorageDriven

UStoreTraversalFieldHandler SduDocumentTW UMarkerEntrypoint (SduEntrypoint store arg) Source # 
Instance details

Defined in Lorentz.Contracts.Upgradeable.StorageDriven

type ShowUStoreField UMarkerEntrypoint (SduEntrypoint store arg) Source # 
Instance details

Defined in Lorentz.Contracts.Upgradeable.StorageDriven

type ShowUStoreField UMarkerEntrypoint (SduEntrypoint store arg) = (('Text "entrypoint with argument " :<>: 'ShowType arg) :<>: 'Text " over storage ") :<>: 'ShowType store

data SduEntrypoint (store :: Type) (arg :: Type) Source #

An entrypoint which is assumed to be kept in UStore. It accepts a packed argument.

Instances

Instances details
(TypeHasDoc arg, NiceParameterFull arg) => UStoreTraversalFieldHandler SduAddEntrypointDocTW UMarkerEntrypoint (SduEntrypoint store arg) Source # 
Instance details

Defined in Lorentz.Contracts.Upgradeable.StorageDriven

UStoreTraversalFieldHandler SduDocumentTW UMarkerEntrypoint (SduEntrypoint store arg) Source # 
Instance details

Defined in Lorentz.Contracts.Upgradeable.StorageDriven

Eq (SduEntrypoint store arg) Source # 
Instance details

Defined in Lorentz.Contracts.Upgradeable.StorageDriven

Methods

(==) :: SduEntrypoint store arg -> SduEntrypoint store arg -> Bool #

(/=) :: SduEntrypoint store arg -> SduEntrypoint store arg -> Bool #

Generic (SduEntrypoint store arg) Source # 
Instance details

Defined in Lorentz.Contracts.Upgradeable.StorageDriven

Associated Types

type Rep (SduEntrypoint store arg) :: Type -> Type #

Methods

from :: SduEntrypoint store arg -> Rep (SduEntrypoint store arg) x #

to :: Rep (SduEntrypoint store arg) x -> SduEntrypoint store arg #

Wrappable (SduEntrypoint store arg) Source # 
Instance details

Defined in Lorentz.Contracts.Upgradeable.StorageDriven

Associated Types

type Unwrappable (SduEntrypoint store arg) #

IsoValue (SduEntrypoint store arg) Source # 
Instance details

Defined in Lorentz.Contracts.Upgradeable.StorageDriven

Associated Types

type ToT (SduEntrypoint store arg) :: T #

Methods

toVal :: SduEntrypoint store arg -> Value (ToT (SduEntrypoint store arg)) #

fromVal :: Value (ToT (SduEntrypoint store arg)) -> SduEntrypoint store arg #

(Typeable store, Typeable arg, TypeHasDoc (UStore store), TypeHasDoc arg) => TypeHasDoc (SduEntrypoint store arg) Source # 
Instance details

Defined in Lorentz.Contracts.Upgradeable.StorageDriven

Associated Types

type TypeDocFieldDescriptions (SduEntrypoint store arg) :: FieldDescriptions #

type ShowUStoreField UMarkerEntrypoint (SduEntrypoint store arg) Source # 
Instance details

Defined in Lorentz.Contracts.Upgradeable.StorageDriven

type ShowUStoreField UMarkerEntrypoint (SduEntrypoint store arg) = (('Text "entrypoint with argument " :<>: 'ShowType arg) :<>: 'Text " over storage ") :<>: 'ShowType store
type Rep (SduEntrypoint store arg) Source # 
Instance details

Defined in Lorentz.Contracts.Upgradeable.StorageDriven

type Rep (SduEntrypoint store arg)
type Unwrappable (SduEntrypoint store arg) Source # 
Instance details

Defined in Lorentz.Contracts.Upgradeable.StorageDriven

type Unwrappable (SduEntrypoint store arg) = GUnwrappable (Rep (SduEntrypoint store arg))
type ToT (SduEntrypoint store arg) Source # 
Instance details

Defined in Lorentz.Contracts.Upgradeable.StorageDriven

type ToT (SduEntrypoint store arg) = GValueType (Rep (SduEntrypoint store arg))
type TypeDocFieldDescriptions (SduEntrypoint store arg) Source # 
Instance details

Defined in Lorentz.Contracts.Upgradeable.StorageDriven

type TypeDocFieldDescriptions (SduEntrypoint store arg) = '[] :: [(Symbol, (Maybe Symbol, [(Symbol, Symbol)]))]

pattern UStoreEntrypoint :: SduEntrypointUntyped store -> UStoreEntrypoint store arg Source #

Access code of UStoreEntrypoint.

mkSduEntrypoint :: NiceUnpackedValue arg => Entrypoint arg (UStore store) -> SduEntrypoint store arg Source #

Construct public entrypoint.

mkUStoreEntrypoint :: NiceUnpackedValue arg => Entrypoint arg (UStore store) -> UStoreEntrypoint store arg Source #

Construct public entrypoint for UStore.

type SduFallback store = Lambda ((MText, ByteString), UStore store) ([Operation], UStore store) Source #

A helper type that defines a function being called in case no implementation matches the requested entrypoint

type UStoreEpInterface utemplate = ExtractInterface utemplate (PickMarkedFields UMarkerEntrypoint utemplate) Source #

Get the set of entrypoints (i.e. UStoreEntrypoint entries) stored in UStore with given template.

mkSduContract :: Typeable (VerUStoreTemplate ver) => SduFallback (VerUStoreTemplate ver) -> UContractRouter ver Source #

Construct UContractRouter which allows calling all entrypoints stored as UStoreEntrypoint entries of UStore.

callUStoreEntrypoint :: (NicePackedValue arg, HasUField field (SduEntrypoint store arg) store) => Label field -> (arg ': (UStore store ': s)) :-> (([Operation], UStore store) ': s) Source #

Call an entrypoint stored under the given field.

sduFallbackFail :: SduFallback store Source #

Default implementation for SduFallback reports an error just like its UParam counterpart.

Documentation

sduDocument :: UStoreTraversable SduDocumentTW template => template -> Lambda () () Source #

Gather documentation of entrypoints kept in given storage. Unfortunatelly, this seems to be the only place where we can pick the code for documenting it.

Note: in most cases you want to use this function is couple with sduAddEntrypointDoc.

data SduDocumentTW Source #

Instances

Instances details
UStoreTraversalWay SduDocumentTW Source # 
Instance details

Defined in Lorentz.Contracts.Upgradeable.StorageDriven

UStoreTraversalSubmapHandler SduDocumentTW k v Source # 
Instance details

Defined in Lorentz.Contracts.Upgradeable.StorageDriven

UStoreTraversalFieldHandler SduDocumentTW marker v Source # 
Instance details

Defined in Lorentz.Contracts.Upgradeable.StorageDriven

UStoreTraversalFieldHandler SduDocumentTW UMarkerEntrypoint (SduEntrypoint store arg) Source # 
Instance details

Defined in Lorentz.Contracts.Upgradeable.StorageDriven

type UStoreTraversalArgumentWrapper SduDocumentTW Source # 
Instance details

Defined in Lorentz.Contracts.Upgradeable.StorageDriven

type UStoreTraversalMonad SduDocumentTW Source # 
Instance details

Defined in Lorentz.Contracts.Upgradeable.StorageDriven

sduAddEntrypointDoc :: (UStoreTraversable SduAddEntrypointDocTW template, DocItem (DEntrypoint epKind)) => Proxy epKind -> template -> template Source #

Mark all public code kept in given storage as atomic entrypoints.

Sometimes you want your SduEntrypoints to contain multiple sub-entrypoints inside, in this case using entryCase function you get documentation for each of sub-entrypoints automatically and calling this function is not necessary. In case when this does not hold and SduEntrypoint keeps exactly one entrypoint, you still need to mark it as such in order for sduDocument to handle it properly. This function does exactly that - it finds all UStore entrypoints and marks them for documentation.

data SduAddEntrypointDocTW Source #

Instances

Instances details
UStoreTraversalWay SduAddEntrypointDocTW Source # 
Instance details

Defined in Lorentz.Contracts.Upgradeable.StorageDriven

UStoreTraversalSubmapHandler SduAddEntrypointDocTW k v Source # 
Instance details

Defined in Lorentz.Contracts.Upgradeable.StorageDriven

UStoreTraversalFieldHandler SduAddEntrypointDocTW marker v Source # 
Instance details

Defined in Lorentz.Contracts.Upgradeable.StorageDriven

(TypeHasDoc arg, NiceParameterFull arg) => UStoreTraversalFieldHandler SduAddEntrypointDocTW UMarkerEntrypoint (SduEntrypoint store arg) Source # 
Instance details

Defined in Lorentz.Contracts.Upgradeable.StorageDriven

type UStoreTraversalArgumentWrapper SduAddEntrypointDocTW Source # 
Instance details

Defined in Lorentz.Contracts.Upgradeable.StorageDriven

type UStoreTraversalMonad SduAddEntrypointDocTW Source # 
Instance details

Defined in Lorentz.Contracts.Upgradeable.StorageDriven

sduContractDoc :: forall utemplate ver. (NiceVersion ver, KnownContractVersion ver, UStoreTraversable SduDocumentTW utemplate, PermConstraint ver) => utemplate -> PermanentImpl ver -> Lambda () () Source #

By given storage make up a fake contract which contains documentation of all entrypoints declared by this storage.

Note: in most cases you want to use this function in couple with sduAddEntrypointDoc.

Note: we intentionally allow accepted UStore template not to correspond to the contract version storage, this is useful when one does not want to provide the full storage (construction of which may require passing some parameters), rather only part of storage with entrypoints.