Safe Haskell | None |
---|---|
Language | Haskell2010 |
Morley.Michelson.Runtime.GState
Description
Global blockchain state (emulated).
Synopsis
- data ContractState = forall cp st.(ParameterScope cp, StorageScope st) => ContractState {
- csBalance :: Mutez
- csContract :: Contract cp st
- csStorage :: Value st
- csDelegate :: Maybe KeyHash
- data AddressState
- asBalance :: AddressState -> Mutez
- newtype VotingPowers = VotingPowers (Map KeyHash Natural)
- vpPick :: KeyHash -> VotingPowers -> Natural
- vpTotal :: VotingPowers -> Natural
- mkVotingPowers :: [(KeyHash, Natural)] -> VotingPowers
- mkVotingPowersFromMap :: Map KeyHash Natural -> VotingPowers
- dummyVotingPowers :: VotingPowers
- newtype BigMapCounter = BigMapCounter {}
- bigMapCounter :: Iso' BigMapCounter Natural
- data GState = GState {}
- gsChainIdL :: Lens' GState ChainId
- gsAddressesL :: Lens' GState (Map Address AddressState)
- gsVotingPowersL :: Lens' GState VotingPowers
- gsCounterL :: Lens' GState GlobalCounter
- gsBigMapCounterL :: Lens' GState BigMapCounter
- genesisAddresses :: NonEmpty Address
- genesisKeyHashes :: NonEmpty KeyHash
- genesisAddress :: Address
- genesisAddress1 :: Address
- genesisAddress2 :: Address
- genesisAddress3 :: Address
- genesisAddress4 :: Address
- genesisAddress5 :: Address
- genesisAddress6 :: Address
- genesisKeyHash :: KeyHash
- genesisSecretKey :: SecretKey
- genesisSecrets :: NonEmpty SecretKey
- initGState :: GState
- readGState :: FilePath -> IO GState
- writeGState :: FilePath -> GState -> IO ()
- data GStateUpdate where
- GSAddAddress :: Address -> AddressState -> GStateUpdate
- GSSetStorageValue :: StorageScope st => Address -> Value st -> GStateUpdate
- GSSetBalance :: Address -> Mutez -> GStateUpdate
- GSIncrementCounter :: GStateUpdate
- GSUpdateCounter :: GlobalCounter -> GStateUpdate
- GSSetBigMapCounter :: BigMapCounter -> GStateUpdate
- GSSetDelegate :: Address -> Maybe KeyHash -> GStateUpdate
- data GStateUpdateError
- applyUpdate :: GStateUpdate -> GState -> Either GStateUpdateError GState
- applyUpdates :: [GStateUpdate] -> GState -> Either GStateUpdateError GState
- extractAllContracts :: GState -> TcOriginatedContracts
Auxiliary types
data ContractState Source #
State of a contract with code.
Constructors
forall cp st.(ParameterScope cp, StorageScope st) => ContractState | |
Fields
|
Instances
Show ContractState Source # | |
Defined in Morley.Michelson.Runtime.GState Methods showsPrec :: Int -> ContractState -> ShowS # show :: ContractState -> String # showList :: [ContractState] -> ShowS # | |
ToJSON ContractState Source # | |
Defined in Morley.Michelson.Runtime.GState Methods toJSON :: ContractState -> Value # toEncoding :: ContractState -> Encoding # toJSONList :: [ContractState] -> Value # toEncodingList :: [ContractState] -> Encoding # | |
FromJSON ContractState Source # | |
Defined in Morley.Michelson.Runtime.GState Methods parseJSON :: Value -> Parser ContractState # parseJSONList :: Value -> Parser [ContractState] # | |
Buildable ContractState Source # | |
Defined in Morley.Michelson.Runtime.GState Methods build :: ContractState -> Builder # |
data AddressState Source #
State of an arbitrary address.
Constructors
ASSimple Mutez | For contracts without code we store only its balance. |
ASContract ContractState | For contracts with code we store more state represented by
|
Instances
asBalance :: AddressState -> Mutez Source #
Extract balance from AddressState
.
newtype VotingPowers Source #
Distribution of voting power among the contracts.
Voting power reflects the ability of bakers to accept, deny or pass new proposals for protocol updates. I.e. each baker has its vote weight.
This datatype definition may change in future, so its internals are not exported.
Constructors
VotingPowers (Map KeyHash Natural) |
Instances
Show VotingPowers Source # | |
Defined in Morley.Michelson.Runtime.GState Methods showsPrec :: Int -> VotingPowers -> ShowS # show :: VotingPowers -> String # showList :: [VotingPowers] -> ShowS # | |
ToJSON VotingPowers Source # | |
Defined in Morley.Michelson.Runtime.GState Methods toJSON :: VotingPowers -> Value # toEncoding :: VotingPowers -> Encoding # toJSONList :: [VotingPowers] -> Value # toEncodingList :: [VotingPowers] -> Encoding # | |
FromJSON VotingPowers Source # | |
Defined in Morley.Michelson.Runtime.GState |
vpTotal :: VotingPowers -> Natural Source #
Get total voting power.
mkVotingPowers :: [(KeyHash, Natural)] -> VotingPowers Source #
Create voting power distribution.
If some key is encountered multiple times, voting power will be summed up.
mkVotingPowersFromMap :: Map KeyHash Natural -> VotingPowers Source #
Create voting power distribution from map.
dummyVotingPowers :: VotingPowers Source #
Dummy VotingPowers
. We give all the voting power to two genesis addreses
as the addresses holding lot of money. Only two addresses are involved for
simplicity.
newtype BigMapCounter Source #
All big_maps stored in a chain have a globally unique ID.
We use this counter to keep track of how many big_maps have been created so far, and to generate new IDs whenever a new big_map is created.
Constructors
BigMapCounter | |
Fields |
Instances
GState
Persistent data passed to Morley contracts which can be updated as result of contract execution.
Constructors
GState | |
Fields
|
genesisAddresses :: NonEmpty Address Source #
Initially these addresses have a lot of money.
genesisKeyHashes :: NonEmpty KeyHash Source #
KeyHash of genesis address.
genesisAddress :: Address Source #
One of genesis addresses.
More genesisAddresses which can be used in tests
genesisAddress1 :: Address Source #
More genesis addresses
We know size of genesisAddresses
, so it is safe to use !!
genesisAddress2 :: Address Source #
More genesis addresses
We know size of genesisAddresses
, so it is safe to use !!
genesisAddress3 :: Address Source #
More genesis addresses
We know size of genesisAddresses
, so it is safe to use !!
genesisKeyHash :: KeyHash Source #
One of genesis key hashes.
Genesis secret keys
genesisSecretKey :: SecretKey Source #
Secret key assotiated with genesisAddress
.
genesisSecrets :: NonEmpty SecretKey Source #
Secrets from which genesis addresses are derived from.
initGState :: GState Source #
Operations on GState
data GStateUpdate where Source #
Updates that can be applied to GState
.
Constructors
GSAddAddress :: Address -> AddressState -> GStateUpdate | |
GSSetStorageValue :: StorageScope st => Address -> Value st -> GStateUpdate | |
GSSetBalance :: Address -> Mutez -> GStateUpdate | |
GSIncrementCounter :: GStateUpdate | |
GSUpdateCounter :: GlobalCounter -> GStateUpdate | |
GSSetBigMapCounter :: BigMapCounter -> GStateUpdate | |
GSSetDelegate :: Address -> Maybe KeyHash -> GStateUpdate |
Instances
Show GStateUpdate Source # | |
Defined in Morley.Michelson.Runtime.GState Methods showsPrec :: Int -> GStateUpdate -> ShowS # show :: GStateUpdate -> String # showList :: [GStateUpdate] -> ShowS # | |
Buildable GStateUpdate Source # | |
Defined in Morley.Michelson.Runtime.GState Methods build :: GStateUpdate -> Builder # |
data GStateUpdateError Source #
Constructors
GStateAddressExists Address | |
GStateUnknownAddress Address | |
GStateNotContract Address | |
GStateStorageNotMatch Address |
Instances
Show GStateUpdateError Source # | |
Defined in Morley.Michelson.Runtime.GState Methods showsPrec :: Int -> GStateUpdateError -> ShowS # show :: GStateUpdateError -> String # showList :: [GStateUpdateError] -> ShowS # | |
Buildable GStateUpdateError Source # | |
Defined in Morley.Michelson.Runtime.GState Methods build :: GStateUpdateError -> Builder # |
applyUpdate :: GStateUpdate -> GState -> Either GStateUpdateError GState Source #
Apply GStateUpdate
to GState
.
applyUpdates :: [GStateUpdate] -> GState -> Either GStateUpdateError GState Source #
Apply a list of GStateUpdate
s to GState
.
extractAllContracts :: GState -> TcOriginatedContracts Source #
Retrieve all contracts stored in GState