Safe Haskell | None |
---|---|
Language | Haskell2010 |
Impementation of Store
- object incapsulating multiple BigMap
s.
This module also provides template for the contract storage -
StorageSkeleton
.
We represent Store
as big_map bytes (a | b | ...)
.
Key of this map is formed as (index, orig_key)
, where index
is
zero-based index of emulated map, orig_key
is key of this emulated map.
Value of this map is just a union of emulated map's values.
Synopsis
- newtype Store a = Store {
- unStore :: BigMap ByteString a
- data k |-> v
- type GetStoreKey store name = MSKey (GetStore name store)
- type GetStoreValue store name = MSValue (GetStore name store)
- storeMem :: forall store name s. StoreMemC store name => Label name -> (GetStoreKey store name ': (Store store ': s)) :-> (Bool ': s)
- storeGet :: forall store name s. StoreGetC store name => Label name -> (GetStoreKey store name ': (Store store ': s)) :-> (Maybe (GetStoreValue store name) ': s)
- storeInsert :: forall store name s. StoreInsertC store name => Label name -> (GetStoreKey store name ': (GetStoreValue store name ': (Store store ': s))) :-> (Store store ': s)
- storeInsertNew :: forall store name err s. (StoreInsertC store name, KnownSymbol name, KnownValue err) => Label name -> (forall s0. (GetStoreKey store name ': s0) :-> (err ': s0)) -> (GetStoreKey store name ': (GetStoreValue store name ': (Store store ': s))) :-> (Store store ': s)
- storeDelete :: forall store name s. StoreDeleteC store name => Label name -> (GetStoreKey store name ': (Store store ': s)) :-> (Store store ': s)
- type StoreMemC store name = StoreOpC store name
- type StoreGetC store name = (StoreOpC store name, InstrUnwrapC store name, SingI (ToT (GetStoreValue store name)), CtorHasOnlyField name store (GetStoreKey store name |-> GetStoreValue store name))
- type StoreInsertC store name = (StoreOpC store name, InstrWrapC store name, CtorHasOnlyField name store (GetStoreKey store name |-> GetStoreValue store name))
- type StoreDeleteC store name = (StoreOpC store name, SingI (ToT store))
- type HasStore name key value store = (StoreGetC store name, StoreInsertC store name, StoreDeleteC store name, GetStoreKey store name ~ key, GetStoreValue store name ~ value, StorePieceC store name key value)
- type HasStoreForAllIn store constrained = GForAllHasStore constrained (Rep store)
- data StorageSkeleton storeTemplate other = StorageSkeleton {}
- storageUnpack :: (StorageSkeleton store fields ': s) :-> ((Store store, fields) ': s)
- storagePack :: ((Store store, fields) ': s) :-> (StorageSkeleton store fields ': s)
- storageMem :: forall store name fields s. StoreMemC store name => Label name -> (GetStoreKey store name ': (StorageSkeleton store fields ': s)) :-> (Bool ': s)
- storageGet :: forall store name fields s. StoreGetC store name => Label name -> (GetStoreKey store name ': (StorageSkeleton store fields ': s)) :-> (Maybe (GetStoreValue store name) ': s)
- storageInsert :: forall store name fields s. StoreInsertC store name => Label name -> (GetStoreKey store name ': (GetStoreValue store name ': (StorageSkeleton store fields ': s))) :-> (StorageSkeleton store fields ': s)
- storageInsertNew :: forall store name fields err s. (StoreInsertC store name, KnownSymbol name, KnownValue err) => Label name -> (forall s0. (GetStoreKey store name ': s0) :-> (err ': s0)) -> (GetStoreKey store name ': (GetStoreValue store name ': (StorageSkeleton store fields ': s))) :-> (StorageSkeleton store fields ': s)
- storageDelete :: forall store name fields s. StoreDeleteC store name => Label name -> (GetStoreKey store name ': (StorageSkeleton store fields ': s)) :-> (StorageSkeleton store fields ': s)
- storePiece :: forall name store key value. StorePieceC store name key value => Label name -> key -> value -> Store store
- storeLookup :: forall name store key value ctorIdx. (key ~ GetStoreKey store name, value ~ GetStoreValue store name, ctorIdx ~ MSCtorIdx (GetStore name store), IsoValue key, KnownValue key, HasNoOp (ToT key), HasNoBigMap (ToT key), KnownNat ctorIdx, InstrUnwrapC store name, Generic store, CtorOnlyField name store ~ (key |-> value)) => Label name -> key -> Store store -> Maybe value
- type StorePieceC store name key value = (key ~ GetStoreKey store name, value ~ GetStoreValue store name, IsoValue key, KnownValue key, HasNoOp (ToT key), HasNoBigMap (ToT key), KnownNat (MSCtorIdx (GetStore name store)), InstrWrapC store name, Generic store, ExtractCtorField (GetCtorField store name) ~ (key |-> value))
Store and related type definitions
Gathers multple BigMap
s under one object.
Type argument of this datatype stands for a "map template" -
a datatype with multiple constructors, each containing an object of
type |->
and corresponding to single virtual BigMap
.
It's also possible to parameterize it with a larger type which is
a sum of types satisfying the above property.
Inside it keeps only one BigMap
thus not violating Michelson limitations.
See examples below.
Store | |
|
Describes one virtual big map.
Type-lookup-by-name
type GetStoreKey store name = MSKey (GetStore name store) Source #
type GetStoreValue store name = MSValue (GetStore name store) Source #
Instructions
storeMem :: forall store name s. StoreMemC store name => Label name -> (GetStoreKey store name ': (Store store ': s)) :-> (Bool ': s) Source #
storeGet :: forall store name s. StoreGetC store name => Label name -> (GetStoreKey store name ': (Store store ': s)) :-> (Maybe (GetStoreValue store name) ': s) Source #
storeInsert :: forall store name s. StoreInsertC store name => Label name -> (GetStoreKey store name ': (GetStoreValue store name ': (Store store ': s))) :-> (Store store ': s) Source #
storeInsertNew :: forall store name err s. (StoreInsertC store name, KnownSymbol name, KnownValue err) => Label name -> (forall s0. (GetStoreKey store name ': s0) :-> (err ': s0)) -> (GetStoreKey store name ': (GetStoreValue store name ': (Store store ': s))) :-> (Store store ': s) Source #
Insert a key-value pair, but fail if it will overwrite some existing entry.
storeDelete :: forall store name s. StoreDeleteC store name => Label name -> (GetStoreKey store name ': (Store store ': s)) :-> (Store store ': s) Source #
Instruction constraints
type StoreGetC store name = (StoreOpC store name, InstrUnwrapC store name, SingI (ToT (GetStoreValue store name)), CtorHasOnlyField name store (GetStoreKey store name |-> GetStoreValue store name)) Source #
type StoreInsertC store name = (StoreOpC store name, InstrWrapC store name, CtorHasOnlyField name store (GetStoreKey store name |-> GetStoreValue store name)) Source #
type StoreDeleteC store name = (StoreOpC store name, SingI (ToT store)) Source #
type HasStore name key value store = (StoreGetC store name, StoreInsertC store name, StoreDeleteC store name, GetStoreKey store name ~ key, GetStoreValue store name ~ value, StorePieceC store name key value) Source #
This constraint can be used if a function needs to work with big store, but needs to know only about some part(s) of it.
It can use all Store operations for a particular name, key and value without knowing whole template.
type HasStoreForAllIn store constrained = GForAllHasStore constrained (Rep store) Source #
Write down all sensisble constraints which given store
satisfies
and apply them to constrained
.
This store should have |->
datatype in its immediate fields,
no deep inspection is performed.
Storage skeleton
data StorageSkeleton storeTemplate other Source #
Contract storage with big_map
.
Due to Michelson constraints it is the only possible layout containing
big_map
.
Instances
(Eq storeTemplate, Eq other) => Eq (StorageSkeleton storeTemplate other) Source # | |
Defined in Lorentz.Store (==) :: StorageSkeleton storeTemplate other -> StorageSkeleton storeTemplate other -> Bool # (/=) :: StorageSkeleton storeTemplate other -> StorageSkeleton storeTemplate other -> Bool # | |
(Show storeTemplate, Show other) => Show (StorageSkeleton storeTemplate other) Source # | |
Defined in Lorentz.Store showsPrec :: Int -> StorageSkeleton storeTemplate other -> ShowS # show :: StorageSkeleton storeTemplate other -> String # showList :: [StorageSkeleton storeTemplate other] -> ShowS # | |
Generic (StorageSkeleton storeTemplate other) Source # | |
Defined in Lorentz.Store type Rep (StorageSkeleton storeTemplate other) :: Type -> Type # from :: StorageSkeleton storeTemplate other -> Rep (StorageSkeleton storeTemplate other) x # to :: Rep (StorageSkeleton storeTemplate other) x -> StorageSkeleton storeTemplate other # | |
Default other => Default (StorageSkeleton storeTemplate other) Source # | |
Defined in Lorentz.Store def :: StorageSkeleton storeTemplate other # | |
(IsoValue storeTemplate, IsoValue other) => IsoValue (StorageSkeleton storeTemplate other) Source # | |
Defined in Lorentz.Store type ToT (StorageSkeleton storeTemplate other) :: T Source # toVal :: StorageSkeleton storeTemplate other -> Value (ToT (StorageSkeleton storeTemplate other)) Source # fromVal :: Value (ToT (StorageSkeleton storeTemplate other)) -> StorageSkeleton storeTemplate other Source # | |
type Rep (StorageSkeleton storeTemplate other) Source # | |
Defined in Lorentz.Store type Rep (StorageSkeleton storeTemplate other) = D1 (MetaData "StorageSkeleton" "Lorentz.Store" "morley-0.3.0.1-Avb9bjjqJWNEobyGi9OGAh" False) (C1 (MetaCons "StorageSkeleton" PrefixI True) (S1 (MetaSel (Just "sMap") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Store storeTemplate)) :*: S1 (MetaSel (Just "sFields") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 other))) | |
type ToT (StorageSkeleton storeTemplate other) Source # | |
Defined in Lorentz.Store type ToT (StorageSkeleton storeTemplate other) = GValueType (Rep (StorageSkeleton storeTemplate other)) |
storageUnpack :: (StorageSkeleton store fields ': s) :-> ((Store store, fields) ': s) Source #
Unpack StorageSkeleton
into a pair.
storagePack :: ((Store store, fields) ': s) :-> (StorageSkeleton store fields ': s) Source #
Pack a pair into StorageSkeleton
.
storageMem :: forall store name fields s. StoreMemC store name => Label name -> (GetStoreKey store name ': (StorageSkeleton store fields ': s)) :-> (Bool ': s) Source #
storageGet :: forall store name fields s. StoreGetC store name => Label name -> (GetStoreKey store name ': (StorageSkeleton store fields ': s)) :-> (Maybe (GetStoreValue store name) ': s) Source #
storageInsert :: forall store name fields s. StoreInsertC store name => Label name -> (GetStoreKey store name ': (GetStoreValue store name ': (StorageSkeleton store fields ': s))) :-> (StorageSkeleton store fields ': s) Source #
storageInsertNew :: forall store name fields err s. (StoreInsertC store name, KnownSymbol name, KnownValue err) => Label name -> (forall s0. (GetStoreKey store name ': s0) :-> (err ': s0)) -> (GetStoreKey store name ': (GetStoreValue store name ': (StorageSkeleton store fields ': s))) :-> (StorageSkeleton store fields ': s) Source #
Insert a key-value pair, but fail if it will overwrite some existing entry.
storageDelete :: forall store name fields s. StoreDeleteC store name => Label name -> (GetStoreKey store name ': (StorageSkeleton store fields ': s)) :-> (StorageSkeleton store fields ': s) Source #
Store management from Haskell
storePiece :: forall name store key value. StorePieceC store name key value => Label name -> key -> value -> Store store Source #
storeLookup :: forall name store key value ctorIdx. (key ~ GetStoreKey store name, value ~ GetStoreValue store name, ctorIdx ~ MSCtorIdx (GetStore name store), IsoValue key, KnownValue key, HasNoOp (ToT key), HasNoBigMap (ToT key), KnownNat ctorIdx, InstrUnwrapC store name, Generic store, CtorOnlyField name store ~ (key |-> value)) => Label name -> key -> Store store -> Maybe value Source #
Get a value from store by key.
It expects map to be consistent, otherwise call to this function fails with error.
Function constraints
type StorePieceC store name key value = (key ~ GetStoreKey store name, value ~ GetStoreValue store name, IsoValue key, KnownValue key, HasNoOp (ToT key), HasNoBigMap (ToT key), KnownNat (MSCtorIdx (GetStore name store)), InstrWrapC store name, Generic store, ExtractCtorField (GetCtorField store name) ~ (key |-> value)) Source #