Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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
- newtype VotingPowers = VotingPowers (Map KeyHash Natural)
- data ImplicitState = ImplicitState {}
- newtype TicketKey = TicketKey (Address, Value, Ty)
- toTicketKey :: forall t. HasNoOp t => Value ('TTicket t) -> (TicketKey, Natural)
- isBalanceL :: Lens' ImplicitState Mutez
- isDelegateL :: Lens' ImplicitState (Maybe KeyHash)
- isTicketsL :: Lens' ImplicitState (HashMap TicketKey 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 {
- gsChainId :: ChainId
- gsImplicitAddresses :: Map ImplicitAddress ImplicitState
- gsContractAddresses :: Map ContractAddress ContractState
- gsSmartRollupAddresses :: Map SmartRollupAddress ()
- gsVotingPowers :: VotingPowers
- gsCounter :: GlobalCounter
- gsBigMapCounter :: BigMapCounter
- gsImplicitAddressAliases :: Bimap ImplicitAlias ImplicitAddress
- gsContractAddressAliases :: Bimap ContractAlias ContractAddress
- gsChainIdL :: Lens' GState ChainId
- gsImplicitAddressesL :: Lens' GState (Map ImplicitAddress ImplicitState)
- gsContractAddressesL :: Lens' GState (Map ContractAddress ContractState)
- gsImplicitAddressAliasesL :: Lens' GState (Bimap ImplicitAlias ImplicitAddress)
- gsContractAddressAliasesL :: Lens' GState (Bimap ContractAlias ContractAddress)
- gsVotingPowersL :: Lens' GState VotingPowers
- gsCounterL :: Lens' GState GlobalCounter
- gsBigMapCounterL :: Lens' GState BigMapCounter
- addressesL :: KindedAddress kind -> Lens' GState (Map (KindedAddress kind) (AddressStateFam kind))
- genesisAddresses :: GenesisList ImplicitAddress
- genesisKeyHashes :: GenesisList KeyHash
- genesisAddress :: ImplicitAddress
- genesisAddress1 :: ImplicitAddress
- genesisAddress2 :: ImplicitAddress
- genesisAddress3 :: ImplicitAddress
- genesisAddressN :: forall n. (SingIPeano n, (ToPeano GenesisAddressesNum > ToPeano n) ~ 'True) => ImplicitAddress
- genesisKeyHash :: KeyHash
- genesisSecretKey :: SecretKey
- genesisSecrets :: GenesisList SecretKey
- initGState :: GState
- readGState :: FilePath -> IO GState
- writeGState :: FilePath -> GState -> IO ()
- data GStateUpdate where
- GSAddImplicitAddress :: ImplicitAddress -> Mutez -> [(TicketKey, Natural)] -> GStateUpdate
- GSAddContractAddress :: ContractAddress -> ContractState -> GStateUpdate
- GSAddContractAddressAlias :: ContractAlias -> ContractAddress -> GStateUpdate
- GSSetStorageValue :: StorageScope st => ContractAddress -> Value st -> GStateUpdate
- GSSetBalance :: L1AddressKind kind => KindedAddress kind -> Mutez -> GStateUpdate
- GSAddTickets :: ImplicitAddress -> TicketKey -> Natural -> GStateUpdate
- GSRemoveTickets :: ImplicitAddress -> TicketKey -> Natural -> GStateUpdate
- GSIncrementCounter :: GStateUpdate
- GSUpdateCounter :: GlobalCounter -> GStateUpdate
- GSSetBigMapCounter :: BigMapCounter -> GStateUpdate
- GSSetDelegate :: L1AddressKind kind => KindedAddress kind -> Maybe KeyHash -> GStateUpdate
- data GStateUpdateError
- = GStateAddressExists Address
- | GStateUnknownAddress Address
- | GStateStorageNotMatch ContractAddress
- | GStateNotDelegate ImplicitAddress
- | GStateCantDeleteDelegate ImplicitAddress
- | GStateNoBLSDelegate Address KeyHash
- | GStateAlreadySetDelegate L1Address (Maybe KeyHash)
- | GStateInsufficientTickets ImplicitAddress TicketKey ("needs" :! Natural) ("has" :! Natural)
- applyUpdate :: GStateUpdate -> GState -> Either GStateUpdateError GState
- applyUpdates :: [GStateUpdate] -> GState -> Either GStateUpdateError GState
- extractAllContracts :: GState -> TcOriginatedContracts
- lookupBalance :: forall kind. L1AddressKind kind => KindedAddress kind -> GState -> Maybe Mutez
- type family AddressStateFam kind where ...
Auxiliary types
data ContractState Source #
State of a contract with code.
forall cp st.(ParameterScope cp, StorageScope st) => ContractState | |
|
Instances
FromJSON ContractState Source # | |
Defined in Morley.Michelson.Runtime.GState parseJSON :: Value -> Parser ContractState # parseJSONList :: Value -> Parser [ContractState] # | |
ToJSON ContractState Source # | |
Defined in Morley.Michelson.Runtime.GState toJSON :: ContractState -> Value # toEncoding :: ContractState -> Encoding # toJSONList :: [ContractState] -> Value # toEncodingList :: [ContractState] -> Encoding # | |
Show ContractState Source # | |
Defined in Morley.Michelson.Runtime.GState showsPrec :: Int -> ContractState -> ShowS # show :: ContractState -> String # showList :: [ContractState] -> ShowS # | |
Buildable ContractState Source # | |
Defined in Morley.Michelson.Runtime.GState build :: ContractState -> Builder # | |
Eq ContractState Source # | |
Defined in Morley.Michelson.Runtime.GState (==) :: ContractState -> ContractState -> Bool # (/=) :: ContractState -> ContractState -> Bool # |
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.
Instances
FromJSON VotingPowers Source # | |
Defined in Morley.Michelson.Runtime.GState parseJSON :: Value -> Parser VotingPowers # parseJSONList :: Value -> Parser [VotingPowers] # | |
ToJSON VotingPowers Source # | |
Defined in Morley.Michelson.Runtime.GState toJSON :: VotingPowers -> Value # toEncoding :: VotingPowers -> Encoding # toJSONList :: [VotingPowers] -> Value # toEncodingList :: [VotingPowers] -> Encoding # | |
Show VotingPowers Source # | |
Defined in Morley.Michelson.Runtime.GState showsPrec :: Int -> VotingPowers -> ShowS # show :: VotingPowers -> String # showList :: [VotingPowers] -> ShowS # | |
Eq VotingPowers Source # | |
Defined in Morley.Michelson.Runtime.GState (==) :: VotingPowers -> VotingPowers -> Bool # (/=) :: VotingPowers -> VotingPowers -> Bool # |
data ImplicitState Source #
ImplicitState | |
|
Instances
FromJSON ImplicitState Source # | |
Defined in Morley.Michelson.Runtime.GState parseJSON :: Value -> Parser ImplicitState # parseJSONList :: Value -> Parser [ImplicitState] # | |
ToJSON ImplicitState Source # | |
Defined in Morley.Michelson.Runtime.GState toJSON :: ImplicitState -> Value # toEncoding :: ImplicitState -> Encoding # toJSONList :: [ImplicitState] -> Value # toEncodingList :: [ImplicitState] -> Encoding # | |
Show ImplicitState Source # | |
Defined in Morley.Michelson.Runtime.GState showsPrec :: Int -> ImplicitState -> ShowS # show :: ImplicitState -> String # showList :: [ImplicitState] -> ShowS # | |
Buildable ImplicitState Source # | |
Defined in Morley.Michelson.Runtime.GState build :: ImplicitState -> Builder # | |
Eq ImplicitState Source # | |
Defined in Morley.Michelson.Runtime.GState (==) :: ImplicitState -> ImplicitState -> Bool # (/=) :: ImplicitState -> ImplicitState -> Bool # |
A triple of ticketer, value and type, which uniquely defines a ticket.
Instances
toTicketKey :: forall t. HasNoOp t => Value ('TTicket t) -> (TicketKey, Natural) Source #
Convert a typed ticket value to TicketKey
and amount.
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 addresses
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.
Instances
GState
Persistent data passed to Morley contracts which can be updated as result of contract execution.
GState | |
|
addressesL :: KindedAddress kind -> Lens' GState (Map (KindedAddress kind) (AddressStateFam kind)) Source #
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
,
etc.genesisAddress1
== genesisAddressN @1
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 #
Operations on GState
data GStateUpdate where Source #
Updates that can be applied to GState
.
GSAddImplicitAddress :: ImplicitAddress -> Mutez -> [(TicketKey, Natural)] -> GStateUpdate | |
GSAddContractAddress :: ContractAddress -> ContractState -> GStateUpdate | |
GSAddContractAddressAlias :: ContractAlias -> ContractAddress -> GStateUpdate | |
GSSetStorageValue :: StorageScope st => ContractAddress -> Value st -> GStateUpdate | |
GSSetBalance :: L1AddressKind kind => KindedAddress kind -> Mutez -> GStateUpdate | |
GSAddTickets :: ImplicitAddress -> TicketKey -> Natural -> GStateUpdate | |
GSRemoveTickets :: ImplicitAddress -> TicketKey -> Natural -> GStateUpdate | |
GSIncrementCounter :: GStateUpdate | |
GSUpdateCounter :: GlobalCounter -> GStateUpdate | |
GSSetBigMapCounter :: BigMapCounter -> GStateUpdate | |
GSSetDelegate :: L1AddressKind kind => KindedAddress kind -> Maybe KeyHash -> GStateUpdate |
Instances
Show GStateUpdate Source # | |
Defined in Morley.Michelson.Runtime.GState showsPrec :: Int -> GStateUpdate -> ShowS # show :: GStateUpdate -> String # showList :: [GStateUpdate] -> ShowS # | |
Buildable GStateUpdate Source # | |
Defined in Morley.Michelson.Runtime.GState build :: GStateUpdate -> Builder # |
data GStateUpdateError Source #
Instances
Show GStateUpdateError Source # | |
Defined in Morley.Michelson.Runtime.GState showsPrec :: Int -> GStateUpdateError -> ShowS # show :: GStateUpdateError -> String # showList :: [GStateUpdateError] -> ShowS # | |
Buildable GStateUpdateError Source # | |
Defined in Morley.Michelson.Runtime.GState 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
lookupBalance :: forall kind. L1AddressKind kind => KindedAddress kind -> GState -> Maybe Mutez Source #
type family AddressStateFam kind where ... Source #