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

Lorentz.UStore.Types

Description

UStore definition and common type-level stuff.

Synopsis

UStore and related type definitions

newtype UStore (a :: Type) Source #

Gathers multple fields and BigMaps 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.

Constructors

UStore 

Instances

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

Defined in Lorentz.UStore.Instances

Methods

storeFieldOps :: StoreFieldOps (UStore templ) fname ftype #

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

Defined in Lorentz.UStore.Instances

Methods

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

Eq (UStore a) Source # 
Instance details

Defined in Lorentz.UStore.Types

Methods

(==) :: UStore a -> UStore a -> Bool #

(/=) :: UStore a -> UStore a -> Bool #

Show (UStore a) Source # 
Instance details

Defined in Lorentz.UStore.Types

Methods

showsPrec :: Int -> UStore a -> ShowS #

show :: UStore a -> String #

showList :: [UStore a] -> ShowS #

Generic (UStore a) Source # 
Instance details

Defined in Lorentz.UStore.Types

Associated Types

type Rep (UStore a) :: Type -> Type #

Methods

from :: UStore a -> Rep (UStore a) x #

to :: Rep (UStore a) x -> UStore a #

Semigroup (UStore a) Source # 
Instance details

Defined in Lorentz.UStore.Types

Methods

(<>) :: UStore a -> UStore a -> UStore a #

sconcat :: NonEmpty (UStore a) -> UStore a #

stimes :: Integral b => b -> UStore a -> UStore a #

Monoid (UStore a) Source # 
Instance details

Defined in Lorentz.UStore.Types

Methods

mempty :: UStore a #

mappend :: UStore a -> UStore a -> UStore a #

mconcat :: [UStore a] -> UStore a #

Default (UStore a) Source # 
Instance details

Defined in Lorentz.UStore.Types

Methods

def :: UStore a #

Wrappable (UStore a) Source # 
Instance details

Defined in Lorentz.UStore.Types

Associated Types

type Unwrappable (UStore a) #

MemOpHs (UStore a) Source # 
Instance details

Defined in Lorentz.UStore.Types

Associated Types

type MemOpKeyHs (UStore a) #

UpdOpHs (UStore a) Source # 
Instance details

Defined in Lorentz.UStore.Types

Associated Types

type UpdOpKeyHs (UStore a) #

type UpdOpParamsHs (UStore a) #

GetOpHs (UStore a) Source # 
Instance details

Defined in Lorentz.UStore.Types

Associated Types

type GetOpKeyHs (UStore a) #

type GetOpValHs (UStore a) #

HasAnnotation (UStore a) Source # 
Instance details

Defined in Lorentz.UStore.Types

IsoValue (UStore a) Source # 
Instance details

Defined in Lorentz.UStore.Types

Associated Types

type ToT (UStore a) :: T #

Methods

toVal :: UStore a -> Value (ToT (UStore a)) #

fromVal :: Value (ToT (UStore a)) -> UStore a #

UStoreTemplateHasDoc template => TypeHasDoc (UStore template) Source # 
Instance details

Defined in Lorentz.UStore.Doc

Associated Types

type TypeDocFieldDescriptions (UStore template) :: FieldDescriptions #

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

We allow casting between UStore_ and UStore freely.

Instance details

Defined in Lorentz.UStore.Migration.Base

Methods

castDummy :: Proxy (UStore template1) -> Proxy (UStore template2) -> () #

type Rep (UStore a) Source # 
Instance details

Defined in Lorentz.UStore.Types

type Rep (UStore a) = D1 ('MetaData "UStore" "Lorentz.UStore.Types" "morley-upgradeable-0.3-inplace" 'True) (C1 ('MetaCons "UStore" 'PrefixI 'True) (S1 ('MetaSel ('Just "unUStore") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (BigMap ByteString ByteString))))
type Unwrappable (UStore a) Source # 
Instance details

Defined in Lorentz.UStore.Types

type Unwrappable (UStore a) = GUnwrappable (Rep (UStore a))
type MemOpKeyHs (UStore a) Source # 
Instance details

Defined in Lorentz.UStore.Types

type UpdOpParamsHs (UStore a) Source # 
Instance details

Defined in Lorentz.UStore.Types

type UpdOpKeyHs (UStore a) Source # 
Instance details

Defined in Lorentz.UStore.Types

type GetOpValHs (UStore a) Source # 
Instance details

Defined in Lorentz.UStore.Types

type GetOpKeyHs (UStore a) Source # 
Instance details

Defined in Lorentz.UStore.Types

type ToT (UStore a) Source # 
Instance details

Defined in Lorentz.UStore.Types

type TypeDocFieldDescriptions (UStore template) Source # 
Instance details

Defined in Lorentz.UStore.Doc

type TypeDocFieldDescriptions (UStore template) = '[] :: [(Symbol, (Maybe Symbol, [(Symbol, Symbol)]))]

newtype k |~> v Source #

Describes one virtual big map in the storage.

Constructors

UStoreSubMap 

Fields

Instances

Instances details
(CanCastTo k1 k2, CanCastTo v1 v2) => CanCastTo (k1 |~> v1 :: Type) (k2 |~> v2 :: Type) Source # 
Instance details

Defined in Lorentz.UStore.Types

Methods

castDummy :: Proxy (k1 |~> v1) -> Proxy (k2 |~> v2) -> () #

(Eq k, Eq v) => Eq (k |~> v) Source # 
Instance details

Defined in Lorentz.UStore.Types

Methods

(==) :: (k |~> v) -> (k |~> v) -> Bool #

(/=) :: (k |~> v) -> (k |~> v) -> Bool #

(Show k, Show v) => Show (k |~> v) Source # 
Instance details

Defined in Lorentz.UStore.Types

Methods

showsPrec :: Int -> (k |~> v) -> ShowS #

show :: (k |~> v) -> String #

showList :: [k |~> v] -> ShowS #

Default (k |~> v) Source # 
Instance details

Defined in Lorentz.UStore.Types

Methods

def :: k |~> v #

newtype UStoreFieldExt (m :: UStoreMarkerType) (v :: Type) Source #

Describes plain field in the storage.

Constructors

UStoreField 

Fields

Instances

Instances details
(m1 ~ m2, CanCastTo a1 a2) => CanCastTo (UStoreFieldExt m1 a1 :: Type) (UStoreFieldExt m2 a2 :: Type) Source # 
Instance details

Defined in Lorentz.UStore.Types

Methods

castDummy :: Proxy (UStoreFieldExt m1 a1) -> Proxy (UStoreFieldExt m2 a2) -> () #

Eq v => Eq (UStoreFieldExt m v) Source # 
Instance details

Defined in Lorentz.UStore.Types

Show v => Show (UStoreFieldExt m v) Source # 
Instance details

Defined in Lorentz.UStore.Types

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).

Extras

class KnownUStoreMarker (marker :: UStoreMarkerType) where Source #

Allows to specify format of key under which fields of this type are stored. Useful to avoid collisions.

Minimal complete definition

Nothing

Associated Types

type ShowUStoreField marker v :: ErrorMessage Source #

Display type-level information about UStore field with given marker and field value type. Used for error messages.

type ShowUStoreField _ v = 'Text "field of type " :<>: 'ShowType v

Methods

mkFieldMarkerUKey :: MText -> ByteString Source #

By field name derive key under which field should be stored.

mkFieldMarkerUKeyL :: forall marker field. KnownUStoreMarker marker => Label field -> ByteString Source #

Version of mkFieldMarkerUKey which accepts label.

mkFieldUKey :: forall (store :: Type) field. KnownUStoreMarker (GetUStoreFieldMarker store field) => Label field -> ByteString Source #

Shortcut for mkFieldMarkerUKey which accepts not marker but store template and name of entry.

type UStoreSubmapKey k = (MText, k) Source #

What do we serialize when constructing big_map key for accessing an UStore submap.

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.

Marked fields

type PickMarkedFields marker template = GPickMarkedFields marker (Rep template) Source #

Collect all fields with the given marker.

Internals

data ElemSignature Source #

What was found on lookup by constructor name.

This keeps either type arguments of |~> or UStoreField.

type GetUStore name a = MERequireFound name a (GLookupStore name (Rep a)) Source #

Get map signature from the constructor with a given name.

type family MSKey (ms :: ElemSignature) :: Type where ... Source #

Equations

MSKey ('MapSignature k _) = k 
MSKey ('FieldSignature _ _) = TypeError ('Text "Expected UStore submap, but field was referred") 

type family MSValue (ms :: ElemSignature) :: Type where ... Source #

Equations

MSValue ('MapSignature _ v) = v 
MSValue ('FieldSignature _ _) = TypeError ('Text "Expected UStore submap, but field was referred") 

type family FSValue (ms :: ElemSignature) :: Type where ... Source #

Equations

FSValue ('FieldSignature _ v) = v 
FSValue ('MapSignature _ _) = TypeError ('Text "Expected UStore field, but submap was referred") 

type family FSMarker (ms :: ElemSignature) :: UStoreMarkerType where ... Source #

Equations

FSMarker ('FieldSignature m _) = m 
FSMarker ('MapSignature _ _) = TypeError ('Text "Expected UStore field, but submap was referred")