morley-1.18.0: Developer tools for the Michelson Language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Morley.Michelson.Runtime.GState

Description

Global blockchain state (emulated).

Synopsis

Auxiliary types

data ContractState Source #

State of a contract with code.

Constructors

forall cp st.(ParameterScope cp, StorageScope st) => ContractState 

Fields

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.

vpPick :: KeyHash -> VotingPowers -> Natural Source #

Get voting power of the given address.

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 

Instances

Instances details
FromJSON BigMapCounter Source # 
Instance details

Defined in Morley.Michelson.Runtime.GState

ToJSON BigMapCounter Source # 
Instance details

Defined in Morley.Michelson.Runtime.GState

Generic BigMapCounter Source # 
Instance details

Defined in Morley.Michelson.Runtime.GState

Associated Types

type Rep BigMapCounter :: Type -> Type #

Num BigMapCounter Source # 
Instance details

Defined in Morley.Michelson.Runtime.GState

Show BigMapCounter Source # 
Instance details

Defined in Morley.Michelson.Runtime.GState

NFData BigMapCounter Source # 
Instance details

Defined in Morley.Michelson.Runtime.GState

Methods

rnf :: BigMapCounter -> () #

Buildable BigMapCounter Source # 
Instance details

Defined in Morley.Michelson.Runtime.GState

Eq BigMapCounter Source # 
Instance details

Defined in Morley.Michelson.Runtime.GState

type Rep BigMapCounter Source # 
Instance details

Defined in Morley.Michelson.Runtime.GState

type Rep BigMapCounter = D1 ('MetaData "BigMapCounter" "Morley.Michelson.Runtime.GState" "morley-1.18.0-inplace" 'True) (C1 ('MetaCons "BigMapCounter" 'PrefixI 'True) (S1 ('MetaSel ('Just "_bigMapCounter") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural)))

GState

data GState Source #

Persistent data passed to Morley contracts which can be updated as result of contract execution.

Constructors

GState 

Fields

Instances

Instances details
FromJSON GState Source # 
Instance details

Defined in Morley.Michelson.Runtime.GState

ToJSON GState Source # 
Instance details

Defined in Morley.Michelson.Runtime.GState

Show GState Source # 
Instance details

Defined in Morley.Michelson.Runtime.GState

Eq GState Source # 
Instance details

Defined in Morley.Michelson.Runtime.GState

Methods

(==) :: GState -> GState -> Bool #

(/=) :: GState -> GState -> Bool #

genesisAddresses :: GenesisList ImplicitAddress Source #

Initially these addresses have a lot of money.

genesisKeyHashes :: GenesisList KeyHash Source #

KeyHash of genesis address.

genesisAddress :: ImplicitAddress Source #

One of genesis addresses.

More genesisAddresses which can be used in tests

genesisAddress1 :: ImplicitAddress Source #

More genesis addresses

genesisAddress2 :: ImplicitAddress Source #

More genesis addresses

genesisAddress3 :: ImplicitAddress Source #

More genesis addresses

genesisAddressN :: forall n. (SingIPeano n, (ToPeano GenesisAddressesNum > ToPeano n) ~ 'True) => ImplicitAddress Source #

More genesis addresses, via a type-level natural

genesisAddressN @7

Note that genesisAddress == genesisAddressN @0, genesisAddress1 == genesisAddressN @1, etc.

genesisKeyHash :: KeyHash Source #

One of genesis key hashes.

Genesis secret keys

genesisSecretKey :: SecretKey Source #

Secret key assotiated with genesisAddress.

genesisSecrets :: GenesisList SecretKey Source #

Secrets from which genesis addresses are derived from.

initGState :: GState Source #

Initial GState. It's supposed to be used if no GState is provided. It puts plenty of money on each genesis address.

readGState :: FilePath -> IO GState Source #

Read GState from a file.

writeGState :: FilePath -> GState -> IO () Source #

Write GState to a file.

Operations on GState

extractAllContracts :: GState -> TcOriginatedContracts Source #

Retrieve all contracts stored in GState

lookupBalance :: forall kind. L1AddressKind kind => KindedAddress kind -> GState -> Maybe Mutez Source #