diff --git a/docs/alpha/transaction_rollups.rst b/docs/alpha/transaction_rollups.rst index 7a1e23c9bc151ed5e79d919e40bccecf1bfb7b38..c4529d00376e1a493fe68be4d917eeb7d5754b89 100644 --- a/docs/alpha/transaction_rollups.rst +++ b/docs/alpha/transaction_rollups.rst @@ -87,6 +87,74 @@ implementation of optimistic rollups. into formal trades (*i.e.*, sets of ticket transfers that need to happen atomically). +Commitments and rejections +************************** + +In order to ensure that L2 transaction effects are correctly computed, +rollup nodes issue commitments. A commitment is a layer-1 operation +which describes (using a Merkle tree hash) the state of a rollup after +each batch of a block. A commitment also includes the predecessor +commitment's hash and level (except in the case of the first +commitment for a rollup). There is exactly one valid commitment +possible for a given block. + +When a commitment is processed, any pending final commitments are +first applied. This allows finalization to be carbonated. If no +commitments are made, it is possible for inboxes to pile up, possibly +leading to a large enough backlog that finalization would exceed the +gas limit. To prevent this, if there are more than 100 inboxes with +messages but without commitments, no further messages are accepted on +the rollup until a commitment is finalized. + +In order to issue a commitment, a bond is required. One bond can +support any number of commitments on a single rollup (but only one per +block). The bond is collected at the time that a given contract +creates its first commitment is on a rollup. It may be refunded by +another manager operation, once the last commitment from its creator +has been finalized (that is, after its finality period). The bond is +treated just like frozen balances for the purposes of delegation. + +If a commitment is invalid, it may be rejected. A rejection operation +for a commitment names one of the operations of the commitment, and +includes a Merkle proof of its wrongness. A L1 node can then replay +just the transactions of a single batch to determine whether the +rejection is valid. A rejection must be included in a block within +the finality period (30 blocks) of the block that the commitment is +included in. + +In the case of a valid rejection, half of the commitment bond goes to +the rejector. All commitments by the rejected commitment's contract +are then removed, as are all commitments which are transitive +successors of that commitment. Since some of those commitments might +have been issued by different contracts, those contracts too must have +have all of their commitments removed, as well as their successors, +and so forth until the process reaches a fixed point. In practice, we +do not expect this to ever happen, since commitment bonds are +expensive enough to discourage bad commitments. + +Each rejection must be preceded by a prerejection. This is to prevent +bakers from front-running rejections. A prerejection is a hash of: +#. The rejection +#. The contract which will submit the rejection +#. A nonce +The prerejection must be at least one block before the corresponding +rejection. Rejections include the nonce so that their prerejections +can be verified. Prerejections prevent bakers from front-running +rejections and getting bonds without doing their own verification. In +the case that multiple rejections reject the same commitment, the one +with the first pre-rejection gets the reward. + +Withdraw +******** + +Withdrawals are processed during commitment finalization. A layer-2 +withdrawal operation puts the withdrawn tickets onto the **ticket +offramp**. From there, a L1 operation on the ``withdraw`` entrypoint +can return the tickets to the L1 contract. Tickets can stay in the +offramp for an arbitrary length of time, but once they are on the +offramp, they cannot be returned to the rollup without passing through +L1 first. + Getting Started --------------- diff --git a/src/proto_alpha/lib_benchmark/michelson_samplers.ml b/src/proto_alpha/lib_benchmark/michelson_samplers.ml index 9e34f20503f54d097f8f9b40d6f210cb1dee702c..436182ecda326c8eb775514f4870c8411323bc62 100644 --- a/src/proto_alpha/lib_benchmark/michelson_samplers.ml +++ b/src/proto_alpha/lib_benchmark/michelson_samplers.ml @@ -70,6 +70,7 @@ type type_name = | `TKey | `TTimestamp | `TAddress + | `TTx_rollup_l2_address | `TBool | `TPair | `TUnion @@ -510,6 +511,19 @@ end) in {destination = Contract contract; entrypoint = ep} + let tx_rollup_l2_address rng_state = + let open Indexable in + if Base_samplers.uniform_bool rng_state then + Index (Random.State.int32 rng_state Int32.max_int) + else + let seed = + Bytes.init 32 (fun _ -> char_of_int @@ Random.State.int rng_state 255) + in + let secret_key = Bls12_381.Signature.generate_sk seed in + Value + (Tx_rollup_l2_address.of_bls_pk + @@ Bls12_381.Signature.derive_pk secret_key) + let chain_id rng_state = let string = Base_samplers.uniform_string ~nbytes:4 rng_state in Data_encoding.Binary.of_string_exn Script_chain_id.encoding string @@ -534,6 +548,7 @@ end) | Timestamp_t _ -> Michelson_base.timestamp | Bool_t _ -> Base_samplers.uniform_bool | Address_t _ -> address + | Tx_rollup_l2_address_t _ -> tx_rollup_l2_address | Pair_t (left_t, right_t, _) -> M.( let* left_v = value left_t in diff --git a/src/proto_alpha/lib_benchmark/michelson_samplers.mli b/src/proto_alpha/lib_benchmark/michelson_samplers.mli index 4ab6d5bd30beb917690c32fa557789d6f6258890..b6fa027152bfed168a108fc05c1010fe942cef3d 100644 --- a/src/proto_alpha/lib_benchmark/michelson_samplers.mli +++ b/src/proto_alpha/lib_benchmark/michelson_samplers.mli @@ -100,6 +100,7 @@ module Make : functor module Internal_for_tests : sig type type_name = [ `TAddress + | `TTx_rollup_l2_address | `TBig_map | `TBls12_381_fr | `TBls12_381_g1 diff --git a/src/proto_alpha/lib_benchmark/test/test_distribution.ml b/src/proto_alpha/lib_benchmark/test/test_distribution.ml index 2591f85de4c67fa22bd789af561b48438adfe681..f77ae5852130f1fa66b3bd193391f6968e954ff2 100644 --- a/src/proto_alpha/lib_benchmark/test/test_distribution.ml +++ b/src/proto_alpha/lib_benchmark/test/test_distribution.ml @@ -23,6 +23,7 @@ let pp_type_name fmtr (t : type_name) = | `TTicket -> "ticket" | `TMap -> "map" | `TAddress -> "address" + | `TTx_rollup_l2_address -> "tx_rollup_l2_address" | `TContract -> "contract" | `TBls12_381_fr -> "bls12_381_fr" | `TSapling_transaction -> "sapling_transaction" @@ -67,6 +68,7 @@ let rec tnames_of_type : | Script_typed_ir.Key_t _ -> `TKey :: acc | Script_typed_ir.Timestamp_t _ -> `TTimestamp :: acc | Script_typed_ir.Address_t _ -> `TAddress :: acc + | Script_typed_ir.Tx_rollup_l2_address_t _ -> `TTx_rollup_l2_address :: acc | Script_typed_ir.Bool_t _ -> `TBool :: acc | Script_typed_ir.Pair_t (lty, rty, _) -> tnames_of_type lty (tnames_of_type rty (`TPair :: acc)) @@ -114,6 +116,7 @@ and tnames_of_comparable_type : | Script_typed_ir.Timestamp_key _ -> `TTimestamp :: acc | Script_typed_ir.Chain_id_key _ -> `TChain_id :: acc | Script_typed_ir.Address_key _ -> `TAddress :: acc + | Script_typed_ir.Tx_rollup_l2_address_key _ -> `TTx_rollup_l2_address :: acc | Script_typed_ir.Pair_key (lty, rty, _) -> tnames_of_comparable_type lty diff --git a/src/proto_alpha/lib_benchmarks_proto/interpreter_workload.ml b/src/proto_alpha/lib_benchmarks_proto/interpreter_workload.ml index 7e477b2b46f18d168fb4bc566e30bf49bdef14cf..084e124480670ff7c13fc1a3259ee304e69e406f 100644 --- a/src/proto_alpha/lib_benchmarks_proto/interpreter_workload.ml +++ b/src/proto_alpha/lib_benchmarks_proto/interpreter_workload.ml @@ -1140,6 +1140,7 @@ let rec size_of_comparable_value : type a. a comparable_ty -> a -> Size.t = | Key_hash_key _ -> Size.key_hash v | Timestamp_key _ -> Size.timestamp v | Address_key _ -> Size.address v + | Tx_rollup_l2_address_key _ -> Size.tx_rollup_l2_address v | Pair_key (leaf, node, _) -> let (lv, rv) = v in let size = diff --git a/src/proto_alpha/lib_benchmarks_proto/size.ml b/src/proto_alpha/lib_benchmarks_proto/size.ml index 51ead05967e6b6f06fb21b404c9fcb655f98e1b4..b84f29930f87de168ef020f00462378e6fd10342 100644 --- a/src/proto_alpha/lib_benchmarks_proto/size.ml +++ b/src/proto_alpha/lib_benchmarks_proto/size.ml @@ -145,6 +145,8 @@ let address (addr : Script_typed_ir.address) : t = Signature.Public_key_hash.size + String.length (Alpha_context.Entrypoint.to_string entrypoint) +let tx_rollup_l2_address = Tx_rollup_l2_address.Indexable.size + let list (list : 'a Script_typed_ir.boxed_list) : t = list.Script_typed_ir.length diff --git a/src/proto_alpha/lib_client/injection.ml b/src/proto_alpha/lib_client/injection.ml index b7386271af6501807a3446e3a636744e7e532f58..a7929d88a1d86f3844064ce93958288ee7f62a27 100644 --- a/src/proto_alpha/lib_client/injection.ml +++ b/src/proto_alpha/lib_client/injection.ml @@ -313,6 +313,8 @@ let estimated_gas_single (type kind) match result with | Applied (Transaction_result (Transaction_to_contract_result {consumed_gas; _})) + | Applied + (Transaction_result (Transaction_to_tx_rollup_result {consumed_gas; _})) -> Ok consumed_gas | Applied (Origination_result {consumed_gas; _}) -> Ok consumed_gas @@ -325,6 +327,12 @@ let estimated_gas_single (type kind) Ok consumed_gas | Applied (Tx_rollup_submit_batch_result {consumed_gas; _}) -> Ok consumed_gas + | Applied (Tx_rollup_commit_result {consumed_gas; _}) -> Ok consumed_gas + | Applied (Tx_rollup_return_bond_result {consumed_gas; _}) -> + Ok consumed_gas + | Applied (Tx_rollup_rejection_result {consumed_gas; _}) -> Ok consumed_gas + | Applied (Tx_rollup_prerejection_result {consumed_gas; _}) -> + Ok consumed_gas | Applied (Sc_rollup_originate_result {consumed_gas; _}) -> Ok consumed_gas | Applied (Sc_rollup_add_messages_result {consumed_gas; _}) -> Ok consumed_gas @@ -354,6 +362,12 @@ let estimated_storage_single (type kind) ~tx_rollup_origination_size if allocated_destination_contract then Ok (Z.add paid_storage_size_diff origination_size) else Ok paid_storage_size_diff + | Applied (Transaction_result (Transaction_to_tx_rollup_result _)) -> + (* TODO: https://gitlab.com/tezos/tezos/-/issues/2339 + Storage fees for transaction rollup. + We need to charge for newly allocated storage (as we do for + Michelson’s big map). *) + Ok Z.zero | Applied (Origination_result {paid_storage_size_diff; _}) -> Ok (Z.add paid_storage_size_diff origination_size) | Applied (Reveal_result _) -> Ok Z.zero @@ -367,6 +381,10 @@ let estimated_storage_single (type kind) ~tx_rollup_origination_size We need to charge for newly allocated storage (as we do for Michelson’s big map). *) Ok Z.zero + | Applied (Tx_rollup_commit_result _) -> Ok Z.zero + | Applied (Tx_rollup_return_bond_result _) -> Ok Z.zero + | Applied (Tx_rollup_rejection_result _) -> Ok Z.zero + | Applied (Tx_rollup_prerejection_result _) -> Ok Z.zero | Applied (Sc_rollup_originate_result {size; _}) -> Ok size | Applied (Sc_rollup_add_messages_result _) -> Ok Z.zero | Skipped _ -> assert false @@ -411,6 +429,7 @@ let originated_contracts_single (type kind) (Transaction_result (Transaction_to_contract_result {originated_contracts; _})) -> Ok originated_contracts + | Applied (Transaction_result (Transaction_to_tx_rollup_result _)) -> Ok [] | Applied (Origination_result {originated_contracts; _}) -> Ok originated_contracts | Applied (Register_global_constant_result _) -> Ok [] @@ -419,6 +438,10 @@ let originated_contracts_single (type kind) | Applied (Set_deposits_limit_result _) -> Ok [] | Applied (Tx_rollup_origination_result _) -> Ok [] | Applied (Tx_rollup_submit_batch_result _) -> Ok [] + | Applied (Tx_rollup_commit_result _) -> Ok [] + | Applied (Tx_rollup_return_bond_result _) -> Ok [] + | Applied (Tx_rollup_rejection_result _) -> Ok [] + | Applied (Tx_rollup_prerejection_result _) -> Ok [] | Applied (Sc_rollup_originate_result _) -> Ok [] | Applied (Sc_rollup_add_messages_result _) -> Ok [] | Skipped _ -> assert false diff --git a/src/proto_alpha/lib_client/mockup.ml b/src/proto_alpha/lib_client/mockup.ml index 7c9d4eb1126b94d8b1076351f4e4b32eb8a1e37d..556c9ba13bd383a5cde2ef589bd5fb21f18223e6 100644 --- a/src/proto_alpha/lib_client/mockup.ml +++ b/src/proto_alpha/lib_client/mockup.ml @@ -75,6 +75,7 @@ module Protocol_constants_overrides = struct tx_rollup_origination_size : int option; tx_rollup_hard_size_limit_per_inbox : int option; tx_rollup_hard_size_limit_per_message : int option; + tx_rollup_commitment_bond : Tez.t option; sc_rollup_enable : bool option; sc_rollup_origination_size : int option; (* Additional, "bastard" parameters (they are not protocol constants but partially treated the same way). *) @@ -129,7 +130,8 @@ module Protocol_constants_overrides = struct ( ( c.tx_rollup_enable, c.tx_rollup_origination_size, c.tx_rollup_hard_size_limit_per_inbox, - c.tx_rollup_hard_size_limit_per_message ), + c.tx_rollup_hard_size_limit_per_message, + c.tx_rollup_commitment_bond ), (c.sc_rollup_enable, c.sc_rollup_origination_size) ) ) ) ) ) )) (fun ( ( preserved_cycles, @@ -173,7 +175,8 @@ module Protocol_constants_overrides = struct ( ( tx_rollup_enable, tx_rollup_origination_size, tx_rollup_hard_size_limit_per_inbox, - tx_rollup_hard_size_limit_per_message ), + tx_rollup_hard_size_limit_per_message, + tx_rollup_commitment_bond ), (sc_rollup_enable, sc_rollup_origination_size) ) ) ) ) ) ) -> { @@ -216,6 +219,7 @@ module Protocol_constants_overrides = struct tx_rollup_origination_size; tx_rollup_hard_size_limit_per_inbox; tx_rollup_hard_size_limit_per_message; + tx_rollup_commitment_bond; sc_rollup_enable; sc_rollup_origination_size; chain_id; @@ -275,11 +279,12 @@ module Protocol_constants_overrides = struct (opt "cache_stake_distribution_cycles" int8) (opt "cache_sampler_state_cycles" int8)) (merge_objs - (obj4 + (obj5 (opt "tx_rollup_enable" Data_encoding.bool) (opt "tx_rollup_origination_size" int31) (opt "tx_rollup_hard_size_limit_per_inbox" int31) - (opt "tx_rollup_hard_size_limit_per_message" int31)) + (opt "tx_rollup_hard_size_limit_per_message" int31) + (opt "tx_rollup_commitment_bond" Tez.encoding)) (obj2 (opt "sc_rollup_enable" bool) (opt "sc_rollup_origination_size" int31)))))))) @@ -351,6 +356,7 @@ module Protocol_constants_overrides = struct Some parametric.tx_rollup_hard_size_limit_per_inbox; tx_rollup_hard_size_limit_per_message = Some parametric.tx_rollup_hard_size_limit_per_message; + tx_rollup_commitment_bond = Some parametric.tx_rollup_commitment_bond; sc_rollup_enable = Some parametric.sc_rollup_enable; sc_rollup_origination_size = Some parametric.sc_rollup_origination_size; (* Bastard additional parameters. *) @@ -402,6 +408,7 @@ module Protocol_constants_overrides = struct tx_rollup_origination_size = None; tx_rollup_hard_size_limit_per_inbox = None; tx_rollup_hard_size_limit_per_message = None; + tx_rollup_commitment_bond = None; sc_rollup_enable = None; sc_rollup_origination_size = None; chain_id = None; @@ -660,6 +667,12 @@ module Protocol_constants_overrides = struct override_value = o.tx_rollup_hard_size_limit_per_message; pp = pp_print_int; }; + O + { + name = "tx_rollup_commitment_bond"; + override_value = o.tx_rollup_commitment_bond; + pp = Tez.pp; + }; ] in let fields_with_override = @@ -804,6 +817,10 @@ module Protocol_constants_overrides = struct Option.value ~default:c.tx_rollup_hard_size_limit_per_message o.tx_rollup_hard_size_limit_per_message; + tx_rollup_commitment_bond = + Option.value + ~default:c.tx_rollup_commitment_bond + o.tx_rollup_commitment_bond; sc_rollup_enable = Option.value ~default:c.sc_rollup_enable o.sc_rollup_enable; sc_rollup_origination_size = diff --git a/src/proto_alpha/lib_client/operation_result.ml b/src/proto_alpha/lib_client/operation_result.ml index 2b73c4aca0f7a84052b45c89bdd0167dd6c1f12e..16ba5e38af4119ac1a232774af9e2aad3e95231c 100644 --- a/src/proto_alpha/lib_client/operation_result.ml +++ b/src/proto_alpha/lib_client/operation_result.ml @@ -187,6 +187,63 @@ let pp_manager_operation_content (type kind) source internal pp_result ppf source pp_result result + | Tx_rollup_commit {rollup; commitment} -> + Format.fprintf + ppf + "@[%s:%a, %a@,From: %a%a@]" + (if internal then "Internal tx rollup commitment" + else "Tx rollup commitment") + Tx_rollup.pp + rollup + Tx_rollup_commitments.Commitment.pp + commitment + Contract.pp + source + pp_result + result + | Tx_rollup_return_bond {rollup} -> + Format.fprintf + ppf + "@[%s:%a @,From: %a%a@]" + (if internal then "Internal tx rollup return commitment bond" + else "Tx rollup return commitment bond") + Tx_rollup.pp + rollup + Contract.pp + source + pp_result + result + | Tx_rollup_rejection {rollup; level; hash; batch_index; batch = _; nonce} -> + Format.fprintf + ppf + "@[%s:rollup %a level %a commitment %a index %d nonce %Lx @,\ + From: %a%a@]" + (if internal then "Internal tx rollup rejection" + else "Tx rollup rejection") + Tx_rollup.pp + rollup + Raw_level.pp + level + Tx_rollup_commitments.Commitment_hash.pp + hash + batch_index + nonce + Contract.pp + source + pp_result + result + | Tx_rollup_prerejection {hash} -> + Format.fprintf + ppf + "@[%s:hash %a @,From: %a%a@]" + (if internal then "Internal tx rollup prerejection" + else "Tx rollup rejection") + Tx_rollup_rejection.Rejection_hash.pp + hash + Contract.pp + source + pp_result + result | Sc_rollup_originate {kind; boot_sector} -> let (module R : Sc_rollups.PVM.S) = Sc_rollups.of_kind kind in Format.fprintf @@ -278,6 +335,7 @@ let pp_balance_updates ppf = function | Invoice -> "invoices" | Initial_commitments -> "initial commitments" | Minted -> "minted" + | Rollup_bond -> "rollup bond" in let balance = match origin with @@ -384,6 +442,11 @@ let pp_manager_operation_contents_and_result ppf (Z.to_string paid_storage_size_diff) ; Format.fprintf ppf "@,Consumed gas: %a" Gas.Arith.pp consumed_gas ; pp_balance_updates_opt ppf balance_updates + | Transaction_to_tx_rollup_result + {balance_updates; consumed_gas; ticket_hash} -> + Format.fprintf ppf "@,Consumed gas: %a" Gas.Arith.pp consumed_gas ; + pp_balance_updates_opt ppf balance_updates ; + Format.fprintf ppf "@,Ticket hash: %a" Ticket_hash.pp ticket_hash in let pp_origination_result (Origination_result @@ -451,6 +514,42 @@ let pp_manager_operation_contents_and_result ppf balance_updates ; Format.fprintf ppf "@,Consumed gas: %a" Gas.Arith.pp consumed_gas in + let pp_tx_rollup_commit_result + (Tx_rollup_commit_result {balance_updates; consumed_gas}) = + Format.fprintf + ppf + "@,Balance updates:@, %a" + pp_balance_updates + balance_updates ; + Format.fprintf ppf "@,Consumed gas: %a" Gas.Arith.pp consumed_gas + in + let pp_tx_rollup_return_bond_result + (Tx_rollup_return_bond_result {balance_updates; consumed_gas}) = + Format.fprintf + ppf + "@,Balance updates:@, %a" + pp_balance_updates + balance_updates ; + Format.fprintf ppf "@,Consumed gas: %a" Gas.Arith.pp consumed_gas + in + let pp_tx_rollup_rejection_result + (Tx_rollup_rejection_result {balance_updates; consumed_gas}) = + Format.fprintf + ppf + "@,Balance updates:@, %a" + pp_balance_updates + balance_updates ; + Format.fprintf ppf "@,Consumed gas: %a" Gas.Arith.pp consumed_gas + in + let pp_tx_rollup_prerejection_result + (Tx_rollup_prerejection_result {balance_updates; consumed_gas}) = + Format.fprintf + ppf + "@,Balance updates:@, %a" + pp_balance_updates + balance_updates ; + Format.fprintf ppf "@,Consumed gas: %a" Gas.Arith.pp consumed_gas + in let pp_sc_rollup_originate_result (Sc_rollup_originate_result {address; consumed_gas; size; balance_updates}) = @@ -548,6 +647,51 @@ let pp_manager_operation_contents_and_result ppf "@[This rollup submit operation was BACKTRACKED, its expected \ effects (as follow) were NOT applied.@]" ; pp_tx_rollup_submit_batch_result op + | Applied (Tx_rollup_commit_result _ as op) -> + Format.fprintf + ppf + "This tx rollup commit operation was successfully applied" ; + pp_tx_rollup_commit_result op + | Backtracked ((Tx_rollup_commit_result _ as op), _err) -> + Format.fprintf + ppf + "@[This tx rollup commit operation was BACKTRACKED, its \ + expected effects (as follow) were NOT applied.@]" ; + pp_tx_rollup_commit_result op + | Applied (Tx_rollup_return_bond_result _ as op) -> + Format.fprintf + ppf + "This tx rollup return commitment bond operation was successfully \ + applied" ; + pp_tx_rollup_return_bond_result op + | Backtracked ((Tx_rollup_return_bond_result _ as op), _err) -> + Format.fprintf + ppf + "@[This tx rollup return commitment bond operation was \ + BACKTRACKED, its expected effects (as follow) were NOT applied.@]" ; + pp_tx_rollup_return_bond_result op + | Applied (Tx_rollup_rejection_result _ as op) -> + Format.fprintf + ppf + "This tx rollup rejection operation was successfully applied" ; + pp_tx_rollup_rejection_result op + | Backtracked ((Tx_rollup_rejection_result _ as op), _err) -> + Format.fprintf + ppf + "@[This tx rollup rejection operation was BACKTRACKED, its \ + expected effects (as follow) were NOT applied.@]" ; + pp_tx_rollup_rejection_result op + | Applied (Tx_rollup_prerejection_result _ as op) -> + Format.fprintf + ppf + "This tx rollup prerejection operation was successfully applied" ; + pp_tx_rollup_prerejection_result op + | Backtracked ((Tx_rollup_prerejection_result _ as op), _err) -> + Format.fprintf + ppf + "@[This tx rollup prerejection operation was BACKTRACKED, its \ + expected effects (as follow) were NOT applied.@]" ; + pp_tx_rollup_prerejection_result op | Applied (Sc_rollup_originate_result _ as op) -> Format.fprintf ppf diff --git a/src/proto_alpha/lib_parameters/default_parameters.ml b/src/proto_alpha/lib_parameters/default_parameters.ml index bcff5ea4b2a895556f6defb5b775ac1c9875cf75..6f3dcae59c128d7d9e9a07cf89a3d307855c8c96 100644 --- a/src/proto_alpha/lib_parameters/default_parameters.ml +++ b/src/proto_alpha/lib_parameters/default_parameters.ml @@ -104,6 +104,7 @@ let constants_mainnet = (* Transaction rollup’s size limits are expressed in number of bytes *) tx_rollup_hard_size_limit_per_inbox = 100_000; tx_rollup_hard_size_limit_per_message = 5_000; + tx_rollup_commitment_bond = Tez.of_mutez_exn 10_000_000_000L; sc_rollup_enable = false; (* The following value is chosen to prevent spam. *) sc_rollup_origination_size = 6_314; diff --git a/src/proto_alpha/lib_plugin/plugin.ml b/src/proto_alpha/lib_plugin/plugin.ml index 776617f192eb6c00f3e0968c7580ed2d08ccecc1..8ae67f617a0819cb7b1b1c8dae0b18c341c33fe2 100644 --- a/src/proto_alpha/lib_plugin/plugin.ml +++ b/src/proto_alpha/lib_plugin/plugin.ml @@ -1955,6 +1955,8 @@ module RPC = struct | Key_key _meta -> Prim (loc, T_key, [], []) | Timestamp_key _meta -> Prim (loc, T_timestamp, [], []) | Address_key _meta -> Prim (loc, T_address, [], []) + | Tx_rollup_l2_address_key _meta -> + Prim (loc, T_tx_rollup_l2_address, [], []) | Chain_id_key _meta -> Prim (loc, T_chain_id, [], []) | Pair_key (l, r, _meta) -> let tl = unparse_comparable_ty ~loc l in @@ -1988,6 +1990,7 @@ module RPC = struct | Key_t _meta -> return (T_key, [], []) | Timestamp_t _meta -> return (T_timestamp, [], []) | Address_t _meta -> return (T_address, [], []) + | Tx_rollup_l2_address_t _meta -> return (T_tx_rollup_l2_address, [], []) | Operation_t _meta -> return (T_operation, [], []) | Chain_id_t _meta -> return (T_chain_id, [], []) | Never_t _meta -> return (T_never, [], []) diff --git a/src/proto_alpha/lib_protocol/TEZOS_PROTOCOL b/src/proto_alpha/lib_protocol/TEZOS_PROTOCOL index 47a5d4e973f75f9e4e2a30e4d6ccbbb0bcb8d99a..610fc67f101388a068280a4864c5d942ae0f45ec 100644 --- a/src/proto_alpha/lib_protocol/TEZOS_PROTOCOL +++ b/src/proto_alpha/lib_protocol/TEZOS_PROTOCOL @@ -42,15 +42,17 @@ "Cache_memory_helpers", "Contract_repr", "Indexable", + "Entrypoint_repr", "Tx_rollup_l2_address", "Tx_rollup_repr", "Tx_rollup_state_repr", "Tx_rollup_message_repr", "Tx_rollup_inbox_repr", + "Tx_rollup_commitments_repr", + "Tx_rollup_rejection_repr", "Roll_repr_legacy", "Vote_repr", "Block_header_repr", - "Entrypoint_repr", "Destination_repr", "Operation_repr", "Manager_repr", @@ -78,6 +80,7 @@ "Contract_manager_storage", "Delegate_activation_storage", "Frozen_deposits_storage", + "Tx_rollup_frozen_storage", "Stake_storage", "Contract_delegate_storage", "Sapling_storage", @@ -102,6 +105,8 @@ "Global_constants_storage", "Tx_rollup_state_storage", "Tx_rollup_inbox_storage", + "Tx_rollup_commitments_storage", + "Tx_rollup_offramp_storage", "Tx_rollup_storage", "Sc_rollup_storage", diff --git a/src/proto_alpha/lib_protocol/alpha_context.ml b/src/proto_alpha/lib_protocol/alpha_context.ml index 4321bb3f17a084f865d315dbf1452a04fec1c68b..ef24dc6d6e15ddfc0cdd0f6d9c962f59a16c4482 100644 --- a/src/proto_alpha/lib_protocol/alpha_context.ml +++ b/src/proto_alpha/lib_protocol/alpha_context.ml @@ -250,6 +250,20 @@ end module Tx_rollup = struct include Tx_rollup_repr include Tx_rollup_storage + include Tx_rollup_frozen_storage + + let hash_ticket : + Raw_context.t -> + t -> + contents:Script_repr.node -> + ticketer:Script_repr.node -> + ty:Script_repr.node -> + (Ticket_hash_repr.t * Raw_context.t) tzresult = + fun ctxt tx_rollup ~contents ~ticketer ~ty -> + let open Micheline in + let owner = String (dummy_location, to_b58check tx_rollup) in + Ticket_hash_builder.make ctxt ~ticketer ~typ:ty ~contents ~owner + module Internal_for_tests = Tx_rollup_repr end @@ -278,6 +292,12 @@ module Tx_rollup_message = struct Compare.Int.(message_size < message_limit) Tx_rollup_inbox_storage.Tx_rollup_message_size_exceeds_limit >>? fun () -> Ok (message, message_size) + + let make_deposit destination ticket_hash amount = + let deposit = Deposit {destination; ticket_hash; amount} in + (* FIXME: figure out the actual size *) + let size = 48 + 54 + 8 in + (deposit, size) end module Tx_rollup_inbox = struct @@ -285,6 +305,25 @@ module Tx_rollup_inbox = struct include Tx_rollup_inbox_storage end +module Tx_rollup_commitments = struct + include Tx_rollup_commitments_repr + include Tx_rollup_commitments_storage + + module Internal_for_tests = struct + include Tx_rollup_commitments_repr + include Tx_rollup_commitments_storage + end +end + +module Tx_rollup_rejection = struct + include Tx_rollup_rejection_repr + include Tx_rollup_commitments_storage +end + +module Tx_rollup_offramp = struct + include Tx_rollup_offramp_storage +end + module Global_constants_storage = Global_constants_storage module Big_map = struct diff --git a/src/proto_alpha/lib_protocol/alpha_context.mli b/src/proto_alpha/lib_protocol/alpha_context.mli index aa3a2fbd578218bb9f52dab8b92358097dc1dddc..9eb70bbdde66775525b8e9c538828e7f3c0e5d36 100644 --- a/src/proto_alpha/lib_protocol/alpha_context.mli +++ b/src/proto_alpha/lib_protocol/alpha_context.mli @@ -638,6 +638,7 @@ module Script : sig | T_unit | T_operation | T_address + | T_tx_rollup_l2_address | T_sapling_transaction | T_sapling_state | T_chain_id @@ -780,6 +781,7 @@ module Constants : sig tx_rollup_origination_size : int; tx_rollup_hard_size_limit_per_inbox : int; tx_rollup_hard_size_limit_per_message : int; + tx_rollup_commitment_bond : Tez.t; sc_rollup_enable : bool; sc_rollup_origination_size : int; } @@ -871,6 +873,8 @@ module Constants : sig val tx_rollup_hard_size_limit_per_message : context -> int + val tx_rollup_commitment_bond : context -> Tez.t + val sc_rollup_enable : context -> bool val sc_rollup_origination_size : context -> int @@ -1513,6 +1517,7 @@ module Receipt : sig | Invoice | Initial_commitments | Minted + | Rollup_bond val compare_balance : balance -> balance -> int @@ -1949,27 +1954,6 @@ module Ticket_hash : sig (t * context) tzresult end -(** This simply re-exports {!Destination_repr}. *) -module Destination : sig - type t = Contract of Contract.t - - val encoding : t Data_encoding.t - - val pp : Format.formatter -> t -> unit - - val compare : t -> t -> int - - val equal : t -> t -> bool - - val to_b58check : t -> string - - val of_b58check : string -> t tzresult - - val in_memory_size : t -> Cache_memory_helpers.sint - - type error += Invalid_destination_b58check of string -end - (** This module re-exports definitions from {!Tx_rollup_repr} and {!Tx_rollup_storage}. *) module Tx_rollup : sig @@ -1989,11 +1973,50 @@ module Tx_rollup : sig val encoding : tx_rollup Data_encoding.t + val deposit_entrypoint : Entrypoint.t + + type deposit_parameters = { + contents : Script.node; + ty : Script.node; + ticketer : Script.node; + amount : int64; + destination : Tx_rollup_l2_address.Indexable.t; + } + + val withdraw_entrypoint : Entrypoint.t + + type withdraw_parameters = { + contents : Script.node; + ty : Script.node; + ticketer : Script.node; + amount : int64; + destination_contract : Contract.t; + } + + (** [hash_ticket ctxt tx_rollup ~contents ~ticketer ~ty] computes the + hash of the ticket of type [ty ticket], of content [contents] and + of ticketer [ticketer]. + + The goal of the computed hash is twofold: + + {ul {li Identifying the ticket in the layer-2, and} + {li Registering in the table of tickets that [tx_rollup] + owns this ticket.}} *) + val hash_ticket : + context -> + t -> + contents:Script.node -> + ticketer:Script.node -> + ty:Script.node -> + (Ticket_hash.t * context) tzresult + val originate : context -> (context * tx_rollup) tzresult Lwt.t val update_tx_rollups_at_block_finalization : context -> context tzresult Lwt.t + val frozen_tez : context -> Contract.t -> Tez.t tzresult Lwt.t + module Internal_for_tests : sig (** see [tx_rollup_repr.originated_tx_rollup] for documentation *) val originated_tx_rollup : @@ -2010,6 +2033,8 @@ module Tx_rollup_state : sig val encoding : t Data_encoding.t + include Compare.S with type t := t + val pp : Format.formatter -> t -> unit val find : context -> Tx_rollup.t -> (context * t option) tzresult Lwt.t @@ -2018,10 +2043,15 @@ module Tx_rollup_state : sig val update : context -> Tx_rollup.t -> t -> context tzresult Lwt.t + val assert_exist : context -> Tx_rollup.t -> context tzresult Lwt.t + val fees : t -> int -> Tez.t tzresult val last_inbox_level : t -> Raw_level.t option + val first_unfinalized_level : + context -> Tx_rollup.t -> (context * Raw_level.t option) tzresult Lwt.t + type error += | Tx_rollup_already_exists of Tx_rollup.t | Tx_rollup_does_not_exist of Tx_rollup.t @@ -2047,6 +2077,9 @@ module Tx_rollup_message : sig val make_batch : context -> string -> (t * size) tzresult + val make_deposit : + Tx_rollup_l2_address.Indexable.t -> Ticket_hash.t -> int64 -> t * size + val size : t -> int val encoding : t Data_encoding.t @@ -2114,6 +2147,212 @@ module Tx_rollup_inbox : sig | Tx_rollup_message_size_exceeds_limit end +(** This simply re-exports [Tx_rollup_commitments_repr] *) +module Tx_rollup_commitments : sig + module Commitment_hash : sig + val commitment_hash : string + + include S.HASH + end + + module Commitment : sig + type withdrawal = { + contract : Contract.t; + ticket : Ticket_hash.t; + amount : int64; + } + + type batch_commitment = {effects : withdrawal list; root : bytes} + + val batch_commitment_equal : batch_commitment -> batch_commitment -> bool + + type t = { + level : Raw_level.t; + batches : batch_commitment list; + predecessor : Commitment_hash.t option; + } + + val ( = ) : t -> t -> bool + + val pp : Format.formatter -> t -> unit + + val encoding : t Data_encoding.t + + val hash : t -> Commitment_hash.t + end + + type pending_commitment = { + commitment : Commitment.t; + hash : Commitment_hash.t; + committer : Contract.t; + submitted_at : Raw_level.t; + } + + type t = pending_commitment list + + val encoding : t Data_encoding.t + + type error += Commitment_hash_already_submitted + + type error += Two_commitments_from_one_committer + + type error += Wrong_commitment_predecessor_level + + type error += Missing_commitment_predecessor + + type error += Wrong_batch_count + + type error += Retire_uncommitted_level + + type error += No_such_commitment + + type error += Bond_does_not_exist of Contract.t + + type error += Bond_in_use of Contract.t + + type error += Too_many_unfinalized_levels + + type error += No_such_batch of Raw_level.t * int + + val add_commitment : + context -> + Tx_rollup.t -> + Contract.t -> + Commitment.t -> + Tez.t -> + context tzresult Lwt.t + + val reject_commitment : + context -> + Tx_rollup.t -> + Raw_level.t -> + Commitment_hash.t -> + Contract.t -> + Z.t -> + context tzresult Lwt.t + + val get_commitments : + context -> Tx_rollup.t -> Raw_level.t -> (context * t) tzresult Lwt.t + + val pending_bonded_commitments : + context -> Tx_rollup.t -> Contract.t -> (context * int) tzresult Lwt.t + + val finalize_pending_commitments : + context -> Tx_rollup.t -> (context * Contract.t list) tzresult Lwt.t + + val remove_bond : + context -> Tx_rollup.t -> Contract.t -> context tzresult Lwt.t + + val get_commitment_roots : + context -> + Tx_rollup.t -> + Raw_level.t -> + Commitment_hash.t -> + int -> + (context * (Commitment.batch_commitment * Commitment.batch_commitment)) + tzresult + Lwt.t + + module Internal_for_tests : sig + (** See [Tx_rollup_commitments_storage.get_oldest_prerejection] + for documentation *) + val get_oldest_prerejection : context -> Z.t option tzresult Lwt.t + + (** See [Tx_rollup_commitments_storage.retire_rollup_level] + for documentation *) + val retire_rollup_level : + context -> + Tx_rollup.t -> + Raw_level.t -> + Raw_level.t -> + (context * bool) tzresult Lwt.t + end +end + +(** This simply re-exports {!Tx_rollup_rejection_repr}. See + {!Tx_rollup_rejection_repr} for additional documentation of this module. *) +module Tx_rollup_rejection : sig + type error += Wrong_rejection + + type error += Rejection_without_prerejection + + type error += Duplicate_prerejection + + type t = { + rollup : Tx_rollup.t; + level : Raw_level.t; + hash : Tx_rollup_commitments.Commitment_hash.t; + batch_index : int; + batch : Tx_rollup_message.t; + } + + include Compare.S with type t := t + + val encoding : t Data_encoding.t + + module Rejection_hash : sig + val rejection_hash : string + + include S.HASH + end + + val generate_prerejection : + nonce:int64 -> + source:Contract.t -> + rollup:Tx_rollup.t -> + level:Raw_level.t -> + commitment_hash:Tx_rollup_commitments.Commitment_hash.t -> + batch_index:int -> + Rejection_hash.t + + val prereject : context -> Rejection_hash.t -> context tzresult Lwt.t + + val check_prerejection : + context -> t -> int64 -> Contract.t -> (context * Z.t * bool) tzresult Lwt.t +end + +module Tx_rollup_offramp : sig + type error += (* `Permanent *) Withdraw_balance_too_low + + val add_tickets_to_offramp : + context -> + Tx_rollup.t -> + Contract.t -> + Ticket_hash.t -> + int64 -> + context tzresult Lwt.t + + val withdraw : + context -> + Tx_rollup.t -> + Contract.t -> + rollup_ticket_hash:Ticket_hash.t -> + destination_ticket_hash:Ticket_hash.t -> + int64 -> + context tzresult Lwt.t +end + +(** This simply re-exports {!Destination_repr}. *) +module Destination : sig + type t = Contract of Contract.t | Tx_rollup of Tx_rollup.t + + val encoding : t Data_encoding.t + + val pp : Format.formatter -> t -> unit + + val compare : t -> t -> int + + val equal : t -> t -> bool + + val to_b58check : t -> string + + val of_b58check : string -> t tzresult + + val in_memory_size : t -> Cache_memory_helpers.sint + + type error += Invalid_destination_b58check of string +end + module Kind : sig type preendorsement_consensus_kind = Preendorsement_consensus_kind @@ -2164,6 +2403,14 @@ module Kind : sig type tx_rollup_submit_batch = Tx_rollup_submit_batch_kind + type tx_rollup_commit = Tx_rollup_commit_kind + + type tx_rollup_return_bond = Tx_rollup_return_bond_kind + + type tx_rollup_rejection = Tx_rollup_rejection_kind + + type tx_rollup_prerejection = Tx_rollup_prerejection_kind + type sc_rollup_originate = Sc_rollup_originate_kind type sc_rollup_add_messages = Sc_rollup_add_messages_kind @@ -2177,6 +2424,10 @@ module Kind : sig | Set_deposits_limit_manager_kind : set_deposits_limit manager | Tx_rollup_origination_manager_kind : tx_rollup_origination manager | Tx_rollup_submit_batch_manager_kind : tx_rollup_submit_batch manager + | Tx_rollup_commit_manager_kind : tx_rollup_commit manager + | Tx_rollup_return_bond_manager_kind : tx_rollup_return_bond manager + | Tx_rollup_rejection_manager_kind : tx_rollup_rejection manager + | Tx_rollup_prerejection_manager_kind : tx_rollup_prerejection manager | Sc_rollup_originate_manager_kind : sc_rollup_originate manager | Sc_rollup_add_messages_manager_kind : sc_rollup_add_messages manager end @@ -2302,6 +2553,28 @@ and _ manager_operation = content : string; } -> Kind.tx_rollup_submit_batch manager_operation + | Tx_rollup_commit : { + rollup : Tx_rollup.t; + commitment : Tx_rollup_commitments.Commitment.t; + } + -> Kind.tx_rollup_commit manager_operation + | Tx_rollup_return_bond : { + rollup : Tx_rollup.t; + } + -> Kind.tx_rollup_return_bond manager_operation + | Tx_rollup_rejection : { + rollup : Tx_rollup.t; + level : Raw_level.t; + hash : Tx_rollup_commitments.Commitment_hash.t; + batch_index : int; + batch : Tx_rollup_message.t; + nonce : int64; + } + -> Kind.tx_rollup_rejection manager_operation + | Tx_rollup_prerejection : { + hash : Tx_rollup_rejection.Rejection_hash.t; + } + -> Kind.tx_rollup_prerejection manager_operation | Sc_rollup_originate : { kind : Sc_rollup.Kind.t; boot_sector : Sc_rollup.PVM.boot_sector; @@ -2455,6 +2728,16 @@ module Operation : sig val tx_rollup_submit_batch_case : Kind.tx_rollup_submit_batch Kind.manager case + val tx_rollup_commit_case : Kind.tx_rollup_commit Kind.manager case + + val tx_rollup_return_bond_case : + Kind.tx_rollup_return_bond Kind.manager case + + val tx_rollup_rejection_case : Kind.tx_rollup_rejection Kind.manager case + + val tx_rollup_prerejection_case : + Kind.tx_rollup_prerejection Kind.manager case + val register_global_constant_case : Kind.register_global_constant Kind.manager case @@ -2493,6 +2776,14 @@ module Operation : sig val tx_rollup_submit_batch_case : Kind.tx_rollup_submit_batch case + val tx_rollup_commit_case : Kind.tx_rollup_commit case + + val tx_rollup_return_bond_case : Kind.tx_rollup_return_bond case + + val tx_rollup_rejection_case : Kind.tx_rollup_rejection case + + val tx_rollup_prerejection_case : Kind.tx_rollup_prerejection case + val sc_rollup_originate_case : Kind.sc_rollup_originate case val sc_rollup_add_messages_case : Kind.sc_rollup_add_messages case @@ -2683,6 +2974,7 @@ module Token : sig | `Baking_bonuses | `Minted | `Liquidity_baking_subsidies + | `Rollup_bond_return | container ] type sink = @@ -2690,6 +2982,7 @@ module Token : sig | `Double_signing_punishments | `Lost_endorsing_rewards of Signature.Public_key_hash.t * bool * bool | `Burned + | `Rollup_bond | container ] val allocated : context -> container -> bool tzresult Lwt.t diff --git a/src/proto_alpha/lib_protocol/apply.ml b/src/proto_alpha/lib_protocol/apply.ml index 19effe035bbb23aeb75b6b73471c69844e6051eb..0dee20c53a3cbbb75d57cfaf556d536f5e475366 100644 --- a/src/proto_alpha/lib_protocol/apply.ml +++ b/src/proto_alpha/lib_protocol/apply.ml @@ -105,6 +105,10 @@ type error += | (* `Branch *) Empty_transaction of Contract.t | (* `Permanent *) Tx_rollup_feature_disabled + | (* `Permanent *) + Tx_rollup_invalid_transaction_amount + | (* `Permanent *) + Tx_rollup_non_internal_transaction | (* `Permanent *) Sc_rollup_feature_disabled | (* `Permanent *) @@ -494,6 +498,33 @@ let () = (function Tx_rollup_feature_disabled -> Some () | _ -> None) (fun () -> Tx_rollup_feature_disabled) ; + register_error_kind + `Permanent + ~id:"operation.tx_rollup_invalid_transaction_amount" + ~title:"Transaction amount to a transaction rollup must be zero" + ~description: + "Because transaction rollups are outside of the delegation mechanism of \ + Tezos, they cannot own Tez, and therefore transactions targeting a \ + transaction rollup must have its amount field set to zero." + ~pp:(fun ppf () -> + Format.fprintf + ppf + "Transaction amount to a transaction rollup must be zero.") + Data_encoding.unit + (function Tx_rollup_invalid_transaction_amount -> Some () | _ -> None) + (fun () -> Tx_rollup_invalid_transaction_amount) ; + + register_error_kind + `Permanent + ~id:"operation.tx_rollup_non_internal_transaction" + ~title:"Non-internal transaction to a transaction rollup" + ~description:"Non-internal transactions to a tx rollup are forbidden." + ~pp:(fun ppf () -> + Format.fprintf ppf "Transaction to a transaction rollup must be internal.") + Data_encoding.unit + (function Tx_rollup_non_internal_transaction -> Some () | _ -> None) + (fun () -> Tx_rollup_non_internal_transaction) ; + let description = "Smart contract rollups will be enabled in a future proposal." in @@ -1000,6 +1031,102 @@ let apply_manager_operation_content : }) in (ctxt, result, operations) )) + | Transaction {amount; parameters; destination = Tx_rollup dst; entrypoint} -> + assert_tx_rollup_feature_enabled ctxt >>=? fun () -> + fail_unless Tez.(amount = zero) Tx_rollup_invalid_transaction_amount + >>=? fun () -> + if Entrypoint.(entrypoint = Tx_rollup.deposit_entrypoint) then + Script.force_decode_in_context + ~consume_deserialization_gas + ctxt + parameters + >>?= fun (parameters, ctxt) -> + Script_ir_translator.parse_tx_rollup_deposit_parameters ctxt parameters + >>?= fun (Tx_rollup.{ticketer; contents; ty; amount; destination}, ctxt) + -> + Tx_rollup.hash_ticket ctxt dst ~contents ~ticketer ~ty + >>?= fun (ticket_hash, ctxt) -> + Tx_rollup_state.get ctxt dst >>=? fun (ctxt, state) -> + let (deposit, message_size) = + Tx_rollup_message.make_deposit destination ticket_hash amount + in + Tx_rollup_inbox.append_message ctxt dst state deposit + >>=? fun (ctxt, new_state) -> + Tx_rollup_state.update ctxt dst new_state >>=? fun ctxt -> + Ticket_balance.adjust_balance + ctxt + ticket_hash + ~delta:(Z.of_int64 amount) + (* TODO: https://gitlab.com/tezos/tezos/-/issues/2339 + Storage fees for transaction rollup. + We need to charge for newly allocated storage (as we do for + Michelson’s big map). This also means taking into account + the global table of tickets. *) + >>=? + fun (_size, ctxt) -> + Tx_rollup_state.fees new_state message_size >>?= fun cost -> + Token.transfer ctxt (`Contract payer) `Burned cost + >|=? fun (ctxt, balance_updates) -> + let result = + Transaction_result + (Transaction_to_tx_rollup_result + { + balance_updates; + consumed_gas = Gas.consumed ~since:before_operation ~until:ctxt; + ticket_hash; + }) + in + (ctxt, result, []) + else if + Entrypoint.(entrypoint = Alpha_context.Tx_rollup.withdraw_entrypoint) + then + Script.force_decode_in_context + ~consume_deserialization_gas + ctxt + parameters + >>?= fun (parameters, ctxt) -> + Script_ir_translator.parse_tx_rollup_withdraw_parameters ctxt parameters + >>?= fun ( Tx_rollup. + {ticketer; contents; ty; amount; destination_contract}, + ctxt ) -> + Tx_rollup.hash_ticket ctxt dst ~contents ~ticketer ~ty + >>?= fun (rollup_ticket_hash, ctxt) -> + Ticket_balance_key.ticket_balance_key_unparsed + ctxt + ~owner:source + ticketer + ty + contents + >>=? fun (destination_ticket_hash, ctxt) -> + Tx_rollup_offramp.withdraw + ctxt + dst + destination_contract + ~rollup_ticket_hash + ~destination_ticket_hash + amount + (* TODO: https://gitlab.com/tezos/tezos/-/issues/2339 + Storage fees for transaction rollup. + We need to charge for newly allocated storage (as we do for + Michelson’s big map). This also means taking into account + the global table of tickets. *) + >>=? + fun ctxt -> + Tx_rollup_state.get ctxt dst >>=? fun (ctxt, state) -> + Tx_rollup_state.fees state 1 >>?= fun cost -> + Token.transfer ctxt (`Contract payer) `Burned cost + >|=? fun (ctxt, balance_updates) -> + let result = + Transaction_result + (Transaction_to_tx_rollup_result + { + balance_updates; + consumed_gas = Gas.consumed ~since:before_operation ~until:ctxt; + ticket_hash = destination_ticket_hash; + }) + in + (ctxt, result, []) + else fail (Script_tc_errors.No_such_entrypoint entrypoint) | Origination {delegate; script; preorigination; credit} -> Script.force_decode_in_context ~consume_deserialization_gas @@ -1186,6 +1313,101 @@ let apply_manager_operation_content : } in return (ctxt, result, []) + | Tx_rollup_commit {rollup; commitment} -> + Tx_rollup_commitments.finalize_pending_commitments ctxt rollup + >>=? fun (ctxt, to_credit) -> + let bond = Constants.tx_rollup_commitment_bond ctxt in + ( Tx_rollup_commitments.pending_bonded_commitments ctxt rollup source + >>=? fun (ctxt, pending) -> + match pending with + | 0 -> Token.transfer ctxt (`Contract source) `Rollup_bond bond + | _ -> return (ctxt, []) ) + >>=? fun (ctxt, balance_updates) -> + Tez.(bond /? 2L) >>?= fun reward -> + List.fold_left_es + (fun (ctxt, balance_updates) contract -> + Token.transfer ctxt `Rollup_bond_return (`Contract contract) reward + >>=? fun (ctxt, new_balance_updates) -> + return (ctxt, List.append new_balance_updates balance_updates)) + (ctxt, balance_updates) + to_credit + >>=? fun (ctxt, balance_updates) -> + Tx_rollup_commitments.add_commitment ctxt rollup source commitment bond + >>=? fun ctxt -> + let result = + Tx_rollup_commit_result + { + consumed_gas = Gas.consumed ~since:before_operation ~until:ctxt; + balance_updates; + } + in + return (ctxt, result, []) + | Tx_rollup_return_bond {rollup} -> + Tx_rollup_commitments.remove_bond ctxt rollup source >>=? fun ctxt -> + Token.transfer + ctxt + `Rollup_bond_return + (`Contract source) + (Constants.tx_rollup_commitment_bond ctxt) + >>=? fun (ctxt, balance_updates) -> + let result = + Tx_rollup_return_bond_result + { + consumed_gas = Gas.consumed ~since:before_operation ~until:ctxt; + balance_updates; + } + in + return (ctxt, result, []) + | Tx_rollup_rejection {rollup; level; hash; batch_index; batch; nonce} -> + let rejection : Tx_rollup_rejection.t = + {rollup; level; hash; batch_index; batch} + in + Tx_rollup_rejection.check_prerejection ctxt rejection nonce source + >>=? fun (ctxt, priority, exists) -> + (if exists then + Tx_rollup_commitments.get_commitment_roots + ctxt + rollup + level + hash + batch_index + >>=? fun (ctxt, (before_batch, after_batch)) -> + (* TODO replay just this one batch -- for now, we'll assume that + rejection succeeds if before_root = after_root*) + fail_unless + (Tx_rollup_commitments.Commitment.batch_commitment_equal + before_batch + after_batch) + Tx_rollup_rejection.Wrong_rejection + >>=? fun () -> return ctxt + else return ctxt) + >>=? fun ctxt -> + Tx_rollup_commitments.reject_commitment + ctxt + rollup + level + hash + source + priority + >>=? fun ctxt -> + let result = + Tx_rollup_rejection_result + { + consumed_gas = Gas.consumed ~since:before_operation ~until:ctxt; + balance_updates = []; + } + in + return (ctxt, result, []) + | Tx_rollup_prerejection {hash} -> + Tx_rollup_rejection.prereject ctxt hash >>=? fun ctxt -> + let result = + Tx_rollup_prerejection_result + { + consumed_gas = Gas.consumed ~since:before_operation ~until:ctxt; + balance_updates = []; + } + in + return (ctxt, result, []) | Sc_rollup_originate {kind; boot_sector} -> Sc_rollup_operations.originate ctxt ~kind ~boot_sector >>=? fun ({address; size}, ctxt) -> @@ -1281,7 +1503,12 @@ let precheck_manager_contents (type kind) ctxt (op : kind Kind.manager contents) deserialized before (e.g. when retrieve in JSON format). *) (match operation with | Reveal pk -> Contract.reveal_manager_key ctxt source pk - | Transaction {parameters; _} -> + | Transaction {parameters; destination; _} -> + (* Precheck is not called for non-internal operations. *) + fail_when + (match destination with Tx_rollup _ -> true | _ -> false) + Tx_rollup_non_internal_transaction + >>=? fun () -> Lwt.return @@ record_trace Gas_quota_exceeded_init_deserialize @@ (* Fail early if not enough gas for complete deserialization @@ -1327,6 +1554,14 @@ let precheck_manager_contents (type kind) ctxt (op : kind Kind.manager contents) Compare.Int.(String.length content < size_limit) Tx_rollup_inbox.Tx_rollup_message_size_exceeds_limit >|=? fun () -> ctxt + | Tx_rollup_commit _ -> + assert_tx_rollup_feature_enabled ctxt >|=? fun () -> ctxt + | Tx_rollup_return_bond _ -> + assert_tx_rollup_feature_enabled ctxt >|=? fun () -> ctxt + | Tx_rollup_rejection _ -> + assert_tx_rollup_feature_enabled ctxt >|=? fun () -> ctxt + | Tx_rollup_prerejection _ -> + assert_tx_rollup_feature_enabled ctxt >|=? fun () -> ctxt | Sc_rollup_originate _ | Sc_rollup_add_messages _ -> assert_sc_rollup_feature_enabled ctxt >|=? fun () -> ctxt) >>=? fun ctxt -> @@ -1378,6 +1613,11 @@ let burn_storage_fees : allocated_destination_contract = payload.allocated_destination_contract; }) ) + | Transaction_result (Transaction_to_tx_rollup_result _ as payload) -> + (* TODO: https://gitlab.com/tezos/tezos/-/issues/2339 + We need to charge for newly allocated storage (as we do for + Michelson’s big map). *) + return (ctxt, storage_limit, Transaction_result payload) | Origination_result payload -> let consumed = payload.paid_storage_size_diff in let payer = `Contract payer in @@ -1432,6 +1672,14 @@ let burn_storage_fees : We need to charge for newly allocated storage (as we do for Michelson’s big map). *) return (ctxt, storage_limit, Tx_rollup_submit_batch_result payload) + | Tx_rollup_commit_result payload -> + return (ctxt, storage_limit, Tx_rollup_commit_result payload) + | Tx_rollup_return_bond_result payload -> + return (ctxt, storage_limit, Tx_rollup_return_bond_result payload) + | Tx_rollup_rejection_result payload -> + return (ctxt, storage_limit, Tx_rollup_rejection_result payload) + | Tx_rollup_prerejection_result payload -> + return (ctxt, storage_limit, Tx_rollup_prerejection_result payload) | Sc_rollup_originate_result payload -> let payer = `Contract payer in Fees.burn_sc_rollup_origination_fees diff --git a/src/proto_alpha/lib_protocol/apply.mli b/src/proto_alpha/lib_protocol/apply.mli index 8a770e9ed37085751b84c0f73cf1d35f31de449e..80ff4c5cbf65129954034d8d11d627821111b048 100644 --- a/src/proto_alpha/lib_protocol/apply.mli +++ b/src/proto_alpha/lib_protocol/apply.mli @@ -113,6 +113,10 @@ type error += (* `Branch *) Empty_transaction of Contract.t type error += (* `Permanent *) Tx_rollup_feature_disabled +type error += (* `Permanent *) Tx_rollup_invalid_transaction_amount + +type error += (* `Permanent *) Tx_rollup_non_internal_transaction + type error += (* `Permanent *) Sc_rollup_feature_disabled type error += (* `Permanent *) Inconsistent_counters diff --git a/src/proto_alpha/lib_protocol/apply_results.ml b/src/proto_alpha/lib_protocol/apply_results.ml index 4fbed7e51c668e36725edff1ca2186362a98284b..911d4a6fe70abc73fb183b7e15cfa38d7f3774c6 100644 --- a/src/proto_alpha/lib_protocol/apply_results.ml +++ b/src/proto_alpha/lib_protocol/apply_results.ml @@ -57,6 +57,11 @@ type successful_transaction_result = paid_storage_size_diff : Z.t; allocated_destination_contract : bool; } + | Transaction_to_tx_rollup_result of { + ticket_hash : Ticket_hash.t; + balance_updates : Receipt.balance_updates; + consumed_gas : Gas.Arith.fp; + } type _ successful_manager_operation_result = | Reveal_result : { @@ -101,6 +106,26 @@ type _ successful_manager_operation_result = consumed_gas : Gas.Arith.fp; } -> Kind.tx_rollup_submit_batch successful_manager_operation_result + | Tx_rollup_commit_result : { + balance_updates : Receipt.balance_updates; + consumed_gas : Gas.Arith.fp; + } + -> Kind.tx_rollup_commit successful_manager_operation_result + | Tx_rollup_return_bond_result : { + balance_updates : Receipt.balance_updates; + consumed_gas : Gas.Arith.fp; + } + -> Kind.tx_rollup_return_bond successful_manager_operation_result + | Tx_rollup_rejection_result : { + balance_updates : Receipt.balance_updates; + consumed_gas : Gas.Arith.fp; + } + -> Kind.tx_rollup_rejection successful_manager_operation_result + | Tx_rollup_prerejection_result : { + balance_updates : Receipt.balance_updates; + consumed_gas : Gas.Arith.fp; + } + -> Kind.tx_rollup_prerejection successful_manager_operation_result | Sc_rollup_originate_result : { balance_updates : Receipt.balance_updates; address : Sc_rollup.Address.t; @@ -251,7 +276,7 @@ module Manager_result = struct assert (Gas.Arith.(equal (ceil consumed_milligas) consumed_gas)) ; Reveal_result {consumed_gas = consumed_milligas}) - let[@coq_axiom_with_reason "gadt"] transaction_to_contract_case = + let[@coq_axiom_with_reason "gadt"] transaction_contract_variant_cases = union [ case @@ -296,7 +321,8 @@ module Manager_result = struct storage_size, paid_storage_size_diff, allocated_destination_contract, - lazy_storage_diff )) + lazy_storage_diff ) + | _ -> None) (fun ( storage, legacy_lazy_storage_diff, balance_updates, @@ -322,12 +348,33 @@ module Manager_result = struct paid_storage_size_diff; allocated_destination_contract; }); + case + ~title:"To_tx_rollup" + (Tag 1) + (obj4 + (dft "balance_updates" Receipt.balance_updates_encoding []) + (dft "consumed_gas" Gas.Arith.n_integral_encoding Gas.Arith.zero) + (dft "consumed_milligas" Gas.Arith.n_fp_encoding Gas.Arith.zero) + (req "ticket_hash" Ticket_hash.encoding)) + (function + | Transaction_to_tx_rollup_result + {balance_updates; consumed_gas; ticket_hash} -> + Some + ( balance_updates, + Gas.Arith.ceil consumed_gas, + consumed_gas, + ticket_hash ) + | _ -> None) + (fun (balance_updates, consumed_gas, consumed_milligas, ticket_hash) -> + assert (Gas.Arith.(equal (ceil consumed_milligas) consumed_gas)) ; + Transaction_to_tx_rollup_result + {balance_updates; consumed_gas = consumed_milligas; ticket_hash}); ] let[@coq_axiom_with_reason "gadt"] transaction_case = make ~op_case:Operation.Encoding.Manager_operations.transaction_case - ~encoding:transaction_to_contract_case + ~encoding:transaction_contract_variant_cases ~iselect:(function | Internal_operation_result (({operation = Transaction _; _} as op), res) -> @@ -569,6 +616,113 @@ module Manager_result = struct Tx_rollup_submit_batch_result {balance_updates; consumed_gas = consumed_milligas}) + let[@coq_axiom_with_reason "gadt"] tx_rollup_commit_case = + make + ~op_case:Operation.Encoding.Manager_operations.tx_rollup_commit_case + ~encoding: + Data_encoding.( + obj3 + (req "balance_updates" Receipt.balance_updates_encoding) + (dft "consumed_gas" Gas.Arith.n_integral_encoding Gas.Arith.zero) + (dft "consumed_milligas" Gas.Arith.n_fp_encoding Gas.Arith.zero)) + ~iselect:(function + | Internal_operation_result + (({operation = Tx_rollup_commit _; _} as op), res) -> + Some (op, res) + | _ -> None) + ~select:(function + | Successful_manager_result (Tx_rollup_commit_result _ as op) -> Some op + | _ -> None) + ~kind:Kind.Tx_rollup_commit_manager_kind + ~proj:(function + | Tx_rollup_commit_result {balance_updates; consumed_gas} -> + (balance_updates, Gas.Arith.ceil consumed_gas, consumed_gas)) + ~inj:(fun (balance_updates, consumed_gas, consumed_milligas) -> + assert (Gas.Arith.(equal (ceil consumed_milligas) consumed_gas)) ; + Tx_rollup_commit_result + {balance_updates; consumed_gas = consumed_milligas}) + + let[@coq_axiom_with_reason "gadt"] tx_rollup_return_bond_case = + make + ~op_case:Operation.Encoding.Manager_operations.tx_rollup_return_bond_case + ~encoding: + Data_encoding.( + obj3 + (req "balance_updates" Receipt.balance_updates_encoding) + (dft "consumed_gas" Gas.Arith.n_integral_encoding Gas.Arith.zero) + (dft "consumed_milligas" Gas.Arith.n_fp_encoding Gas.Arith.zero)) + ~iselect:(function + | Internal_operation_result + (({operation = Tx_rollup_return_bond _; _} as op), res) -> + Some (op, res) + | _ -> None) + ~select:(function + | Successful_manager_result (Tx_rollup_return_bond_result _ as op) -> + Some op + | _ -> None) + ~kind:Kind.Tx_rollup_return_bond_manager_kind + ~proj:(function + | Tx_rollup_return_bond_result {balance_updates; consumed_gas} -> + (balance_updates, Gas.Arith.ceil consumed_gas, consumed_gas)) + ~inj:(fun (balance_updates, consumed_gas, consumed_milligas) -> + assert (Gas.Arith.(equal (ceil consumed_milligas) consumed_gas)) ; + Tx_rollup_return_bond_result + {balance_updates; consumed_gas = consumed_milligas}) + + let[@coq_axiom_with_reason "gadt"] tx_rollup_rejection_case = + make + ~op_case:Operation.Encoding.Manager_operations.tx_rollup_rejection_case + ~encoding: + Data_encoding.( + obj3 + (req "balance_updates" Receipt.balance_updates_encoding) + (dft "consumed_gas" Gas.Arith.n_integral_encoding Gas.Arith.zero) + (dft "consumed_milligas" Gas.Arith.n_fp_encoding Gas.Arith.zero)) + ~iselect:(function + | Internal_operation_result + (({operation = Tx_rollup_rejection _; _} as op), res) -> + Some (op, res) + | _ -> None) + ~select:(function + | Successful_manager_result (Tx_rollup_rejection_result _ as op) -> + Some op + | _ -> None) + ~kind:Kind.Tx_rollup_rejection_manager_kind + ~proj:(function + | Tx_rollup_rejection_result {balance_updates; consumed_gas} -> + (balance_updates, Gas.Arith.ceil consumed_gas, consumed_gas)) + ~inj:(fun (balance_updates, consumed_gas, consumed_milligas) -> + assert (Gas.Arith.(equal (ceil consumed_milligas) consumed_gas)) ; + Tx_rollup_rejection_result + {balance_updates; consumed_gas = consumed_milligas}) + + let[@coq_axiom_with_reason "gadt"] tx_rollup_prerejection_case = + make + ~op_case:Operation.Encoding.Manager_operations.tx_rollup_prerejection_case + ~encoding: + Data_encoding.( + obj3 + (req "balance_updates" Receipt.balance_updates_encoding) + (dft "consumed_gas" Gas.Arith.n_integral_encoding Gas.Arith.zero) + (dft "consumed_milligas" Gas.Arith.n_fp_encoding Gas.Arith.zero)) + ~iselect:(function + | Internal_operation_result + (({operation = Tx_rollup_prerejection _; _} as op), res) -> + Some (op, res) + | _ -> None) + ~select:(function + | Successful_manager_result (Tx_rollup_prerejection_result _ as op) -> + Some op + | _ -> None) + ~kind:Kind.Tx_rollup_prerejection_manager_kind + ~proj:(function + | Tx_rollup_prerejection_result {balance_updates; consumed_gas} -> + (balance_updates, Gas.Arith.ceil consumed_gas, consumed_gas)) + ~inj:(fun (balance_updates, consumed_gas, consumed_milligas) -> + assert (Gas.Arith.(equal (ceil consumed_milligas) consumed_gas)) ; + Tx_rollup_prerejection_result + {balance_updates; consumed_gas = consumed_milligas}) + let[@coq_axiom_with_reason "gadt"] sc_rollup_originate_case = make ~op_case:Operation.Encoding.Manager_operations.sc_rollup_originate_case @@ -773,6 +927,21 @@ let equal_manager_kind : Kind.Tx_rollup_submit_batch_manager_kind ) -> Some Eq | (Kind.Tx_rollup_submit_batch_manager_kind, _) -> None + | (Kind.Tx_rollup_commit_manager_kind, Kind.Tx_rollup_commit_manager_kind) -> + Some Eq + | (Kind.Tx_rollup_commit_manager_kind, _) -> None + | ( Kind.Tx_rollup_return_bond_manager_kind, + Kind.Tx_rollup_return_bond_manager_kind ) -> + Some Eq + | (Kind.Tx_rollup_return_bond_manager_kind, _) -> None + | ( Kind.Tx_rollup_rejection_manager_kind, + Kind.Tx_rollup_rejection_manager_kind ) -> + Some Eq + | (Kind.Tx_rollup_rejection_manager_kind, _) -> None + | ( Kind.Tx_rollup_prerejection_manager_kind, + Kind.Tx_rollup_prerejection_manager_kind ) -> + Some Eq + | (Kind.Tx_rollup_prerejection_manager_kind, _) -> None | ( Kind.Sc_rollup_originate_manager_kind, Kind.Sc_rollup_originate_manager_kind ) -> Some Eq @@ -1154,6 +1323,50 @@ module Encoding = struct Some (op, res) | _ -> None) + let[@coq_axiom_with_reason "gadt"] tx_rollup_commit_case = + make_manager_case + Operation.Encoding.tx_rollup_commit_case + Manager_result.tx_rollup_commit_case + (function + | Contents_and_result + ((Manager_operation {operation = Tx_rollup_commit _; _} as op), res) + -> + Some (op, res) + | _ -> None) + + let[@coq_axiom_with_reason "gadt"] tx_rollup_return_bond_case = + make_manager_case + Operation.Encoding.tx_rollup_return_bond_case + Manager_result.tx_rollup_return_bond_case + (function + | Contents_and_result + ( (Manager_operation {operation = Tx_rollup_return_bond _; _} as op), + res ) -> + Some (op, res) + | _ -> None) + + let[@coq_axiom_with_reason "gadt"] tx_rollup_rejection_case = + make_manager_case + Operation.Encoding.tx_rollup_rejection_case + Manager_result.tx_rollup_rejection_case + (function + | Contents_and_result + ( (Manager_operation {operation = Tx_rollup_rejection _; _} as op), + res ) -> + Some (op, res) + | _ -> None) + + let[@coq_axiom_with_reason "gadt"] tx_rollup_prerejection_case = + make_manager_case + Operation.Encoding.tx_rollup_prerejection_case + Manager_result.tx_rollup_prerejection_case + (function + | Contents_and_result + ( (Manager_operation {operation = Tx_rollup_prerejection _; _} as op), + res ) -> + Some (op, res) + | _ -> None) + let[@coq_axiom_with_reason "gadt"] sc_rollup_originate_case = make_manager_case Operation.Encoding.sc_rollup_originate_case @@ -1213,6 +1426,10 @@ let contents_result_encoding = make set_deposits_limit_case; make tx_rollup_origination_case; make tx_rollup_submit_batch_case; + make tx_rollup_commit_case; + make tx_rollup_return_bond_case; + make tx_rollup_rejection_case; + make tx_rollup_prerejection_case; make sc_rollup_originate_case; make sc_rollup_add_messages_case; ] @@ -1258,6 +1475,10 @@ let contents_and_result_encoding = make set_deposits_limit_case; make tx_rollup_origination_case; make tx_rollup_submit_batch_case; + make tx_rollup_commit_case; + make tx_rollup_return_bond_case; + make tx_rollup_rejection_case; + make tx_rollup_prerejection_case; make sc_rollup_originate_case; make sc_rollup_add_messages_case; ] @@ -1589,6 +1810,109 @@ let kind_equal : } ) -> Some Eq | (Manager_operation {operation = Tx_rollup_submit_batch _; _}, _) -> None + | ( Manager_operation {operation = Tx_rollup_commit _; _}, + Manager_operation_result + {operation_result = Applied (Tx_rollup_commit_result _); _} ) -> + Some Eq + | ( Manager_operation {operation = Tx_rollup_commit _; _}, + Manager_operation_result + {operation_result = Backtracked (Tx_rollup_commit_result _, _); _} ) -> + Some Eq + | ( Manager_operation {operation = Tx_rollup_commit _; _}, + Manager_operation_result + { + operation_result = + Failed (Alpha_context.Kind.Tx_rollup_commit_manager_kind, _); + _; + } ) -> + Some Eq + | ( Manager_operation {operation = Tx_rollup_commit _; _}, + Manager_operation_result + { + operation_result = + Skipped Alpha_context.Kind.Tx_rollup_commit_manager_kind; + _; + } ) -> + Some Eq + | (Manager_operation {operation = Tx_rollup_commit _; _}, _) -> None + | ( Manager_operation {operation = Tx_rollup_return_bond _; _}, + Manager_operation_result + {operation_result = Applied (Tx_rollup_return_bond_result _); _} ) -> + Some Eq + | ( Manager_operation {operation = Tx_rollup_return_bond _; _}, + Manager_operation_result + {operation_result = Backtracked (Tx_rollup_return_bond_result _, _); _} + ) -> + Some Eq + | ( Manager_operation {operation = Tx_rollup_return_bond _; _}, + Manager_operation_result + { + operation_result = + Failed (Alpha_context.Kind.Tx_rollup_return_bond_manager_kind, _); + _; + } ) -> + Some Eq + | ( Manager_operation {operation = Tx_rollup_return_bond _; _}, + Manager_operation_result + { + operation_result = + Skipped Alpha_context.Kind.Tx_rollup_return_bond_manager_kind; + _; + } ) -> + Some Eq + | (Manager_operation {operation = Tx_rollup_return_bond _; _}, _) -> None + | ( Manager_operation {operation = Tx_rollup_rejection _; _}, + Manager_operation_result + {operation_result = Applied (Tx_rollup_rejection_result _); _} ) -> + Some Eq + | ( Manager_operation {operation = Tx_rollup_rejection _; _}, + Manager_operation_result + {operation_result = Backtracked (Tx_rollup_rejection_result _, _); _} ) + -> + Some Eq + | ( Manager_operation {operation = Tx_rollup_rejection _; _}, + Manager_operation_result + { + operation_result = + Failed (Alpha_context.Kind.Tx_rollup_rejection_manager_kind, _); + _; + } ) -> + Some Eq + | ( Manager_operation {operation = Tx_rollup_rejection _; _}, + Manager_operation_result + { + operation_result = + Skipped Alpha_context.Kind.Tx_rollup_rejection_manager_kind; + _; + } ) -> + Some Eq + | (Manager_operation {operation = Tx_rollup_rejection _; _}, _) -> None + | ( Manager_operation {operation = Tx_rollup_prerejection _; _}, + Manager_operation_result + {operation_result = Applied (Tx_rollup_prerejection_result _); _} ) -> + Some Eq + | ( Manager_operation {operation = Tx_rollup_prerejection _; _}, + Manager_operation_result + {operation_result = Backtracked (Tx_rollup_prerejection_result _, _); _} + ) -> + Some Eq + | ( Manager_operation {operation = Tx_rollup_prerejection _; _}, + Manager_operation_result + { + operation_result = + Failed (Alpha_context.Kind.Tx_rollup_prerejection_manager_kind, _); + _; + } ) -> + Some Eq + | ( Manager_operation {operation = Tx_rollup_prerejection _; _}, + Manager_operation_result + { + operation_result = + Skipped Alpha_context.Kind.Tx_rollup_prerejection_manager_kind; + _; + } ) -> + Some Eq + | (Manager_operation {operation = Tx_rollup_prerejection _; _}, _) -> None | ( Manager_operation {operation = Sc_rollup_originate _; _}, Manager_operation_result {operation_result = Applied (Sc_rollup_originate_result _); _} ) -> diff --git a/src/proto_alpha/lib_protocol/apply_results.mli b/src/proto_alpha/lib_protocol/apply_results.mli index 47a7cafc2952f35e210985d6b64eab4d0bc5e406..5d87d8329550c461b94d7d1e8918b04a5433e785 100644 --- a/src/proto_alpha/lib_protocol/apply_results.mli +++ b/src/proto_alpha/lib_protocol/apply_results.mli @@ -116,6 +116,15 @@ and successful_transaction_result = paid_storage_size_diff : Z.t; allocated_destination_contract : bool; } + (* TODO: https://gitlab.com/tezos/tezos/-/issues/2339 + Storage fees for transaction rollup. + We need to charge for newly allocated storage (as we do for + Michelson’s big map). *) + | Transaction_to_tx_rollup_result of { + ticket_hash : Ticket_hash.t; + balance_updates : Receipt.balance_updates; + consumed_gas : Gas.Arith.fp; + } (** Result of applying a {!manager_operation_content}, either internal or external. *) @@ -174,6 +183,26 @@ and _ successful_manager_operation_result = consumed_gas : Gas.Arith.fp; } -> Kind.tx_rollup_submit_batch successful_manager_operation_result + | Tx_rollup_commit_result : { + balance_updates : Receipt.balance_updates; + consumed_gas : Gas.Arith.fp; + } + -> Kind.tx_rollup_commit successful_manager_operation_result + | Tx_rollup_return_bond_result : { + balance_updates : Receipt.balance_updates; + consumed_gas : Gas.Arith.fp; + } + -> Kind.tx_rollup_return_bond successful_manager_operation_result + | Tx_rollup_rejection_result : { + balance_updates : Receipt.balance_updates; + consumed_gas : Gas.Arith.fp; + } + -> Kind.tx_rollup_rejection successful_manager_operation_result + | Tx_rollup_prerejection_result : { + balance_updates : Receipt.balance_updates; + consumed_gas : Gas.Arith.fp; + } + -> Kind.tx_rollup_prerejection successful_manager_operation_result | Sc_rollup_originate_result : { balance_updates : Receipt.balance_updates; address : Sc_rollup.Address.t; diff --git a/src/proto_alpha/lib_protocol/constants_repr.ml b/src/proto_alpha/lib_protocol/constants_repr.ml index 11d7cdf0ee57d1796c194ef368661ece920f8577..96234ff314b0efa462bf0fec01d00ae396af159a 100644 --- a/src/proto_alpha/lib_protocol/constants_repr.ml +++ b/src/proto_alpha/lib_protocol/constants_repr.ml @@ -162,6 +162,7 @@ type parametric = { tx_rollup_origination_size : int; tx_rollup_hard_size_limit_per_inbox : int; tx_rollup_hard_size_limit_per_message : int; + tx_rollup_commitment_bond : Tez_repr.t; sc_rollup_enable : bool; sc_rollup_origination_size : int; } @@ -209,7 +210,8 @@ let parametric_encoding = ( ( c.tx_rollup_enable, c.tx_rollup_origination_size, c.tx_rollup_hard_size_limit_per_inbox, - c.tx_rollup_hard_size_limit_per_message ), + c.tx_rollup_hard_size_limit_per_message, + c.tx_rollup_commitment_bond ), (c.sc_rollup_enable, c.sc_rollup_origination_size) ) ) ) ) ) )) (fun ( ( preserved_cycles, @@ -251,7 +253,8 @@ let parametric_encoding = ( ( tx_rollup_enable, tx_rollup_origination_size, tx_rollup_hard_size_limit_per_inbox, - tx_rollup_hard_size_limit_per_message ), + tx_rollup_hard_size_limit_per_message, + tx_rollup_commitment_bond ), (sc_rollup_enable, sc_rollup_origination_size) ) ) ) ) ) ) -> { preserved_cycles; @@ -294,6 +297,7 @@ let parametric_encoding = tx_rollup_origination_size; tx_rollup_hard_size_limit_per_inbox; tx_rollup_hard_size_limit_per_message; + tx_rollup_commitment_bond; sc_rollup_enable; sc_rollup_origination_size; }) @@ -350,11 +354,12 @@ let parametric_encoding = (req "cache_stake_distribution_cycles" int8) (req "cache_sampler_state_cycles" int8)) (merge_objs - (obj4 + (obj5 (req "tx_rollup_enable" bool) (req "tx_rollup_origination_size" int31) (req "tx_rollup_hard_size_limit_per_inbox" int31) - (req "tx_rollup_hard_size_limit_per_message" int31)) + (req "tx_rollup_hard_size_limit_per_message" int31) + (req "tx_rollup_commitment_bond" Tez_repr.encoding)) (obj2 (req "sc_rollup_enable" bool) (req "sc_rollup_origination_size" int31)))))))) diff --git a/src/proto_alpha/lib_protocol/constants_repr.mli b/src/proto_alpha/lib_protocol/constants_repr.mli index 062306c4a7d34beb9c9e8fb4e625a773faa0c9fd..78756176e78ea4f252caea5de4baa7be3919825e 100644 --- a/src/proto_alpha/lib_protocol/constants_repr.mli +++ b/src/proto_alpha/lib_protocol/constants_repr.mli @@ -127,6 +127,8 @@ type parametric = { tx_rollup_hard_size_limit_per_inbox : int; (* the maximum amount of bytes one batch can allocate in an inbox *) tx_rollup_hard_size_limit_per_message : int; + (* the amount of tez to bond a tx rollup commitment *) + tx_rollup_commitment_bond : Tez_repr.t; sc_rollup_enable : bool; sc_rollup_origination_size : int; } diff --git a/src/proto_alpha/lib_protocol/constants_storage.ml b/src/proto_alpha/lib_protocol/constants_storage.ml index 50a01c127defdf95cde08b3daf0c1c6b98182b7e..7c5dd10e8cace4bdd7606a0a0ba40a17f1998f06 100644 --- a/src/proto_alpha/lib_protocol/constants_storage.ml +++ b/src/proto_alpha/lib_protocol/constants_storage.ml @@ -161,6 +161,10 @@ let tx_rollup_hard_size_limit_per_message c = let constants = Raw_context.constants c in constants.tx_rollup_hard_size_limit_per_message +let tx_rollup_commitment_bond c = + let constants = Raw_context.constants c in + constants.tx_rollup_commitment_bond + let ratio_of_frozen_deposits_slashed_per_double_endorsement c = let constants = Raw_context.constants c in constants.ratio_of_frozen_deposits_slashed_per_double_endorsement diff --git a/src/proto_alpha/lib_protocol/constants_storage.mli b/src/proto_alpha/lib_protocol/constants_storage.mli index 7772926806c619e91aed47931d13d941f97526ca..87e53d43353fd86617553b849128de7d6b9d9390 100644 --- a/src/proto_alpha/lib_protocol/constants_storage.mli +++ b/src/proto_alpha/lib_protocol/constants_storage.mli @@ -91,6 +91,8 @@ val tx_rollup_hard_size_limit_per_inbox : Raw_context.t -> int val tx_rollup_hard_size_limit_per_message : Raw_context.t -> int +val tx_rollup_commitment_bond : Raw_context.t -> Tez_repr.t + val ratio_of_frozen_deposits_slashed_per_double_endorsement : Raw_context.t -> Constants_repr.ratio diff --git a/src/proto_alpha/lib_protocol/delegate_storage.ml b/src/proto_alpha/lib_protocol/delegate_storage.ml index acc286a84d27ff0e79de803e81f44cdd4f2876fc..b7beaae6c803b657c3368b094c7c01d0cef94adf 100644 --- a/src/proto_alpha/lib_protocol/delegate_storage.ml +++ b/src/proto_alpha/lib_protocol/delegate_storage.ml @@ -537,10 +537,7 @@ let balance ctxt delegate = let frozen_deposits ctxt delegate = Frozen_deposits_storage.get ctxt (Contract_repr.implicit_contract delegate) -let full_balance ctxt delegate = - frozen_deposits ctxt delegate >>=? fun frozen_deposits -> - balance ctxt delegate >>=? fun balance -> - Lwt.return Tez_repr.(frozen_deposits.current_amount +? balance) +let full_balance ctxt delegate = Stake_storage.full_balance ctxt delegate let deactivated = Delegate_activation_storage.is_inactive diff --git a/src/proto_alpha/lib_protocol/destination_repr.ml b/src/proto_alpha/lib_protocol/destination_repr.ml index ff1ba4e1c9dece14f757b6324c098db29d7374e8..3ceeae9a5e1ec7ddfda777e9d8c5edd14ef8b934 100644 --- a/src/proto_alpha/lib_protocol/destination_repr.ml +++ b/src/proto_alpha/lib_protocol/destination_repr.ml @@ -25,7 +25,7 @@ (* *) (*****************************************************************************) -type t = Contract of Contract_repr.t +type t = Contract of Contract_repr.t | Tx_rollup of Tx_rollup_repr.t include Compare.Make (struct type nonrec t = t @@ -33,9 +33,21 @@ include Compare.Make (struct let compare l1 l2 = match (l1, l2) with | (Contract k1, Contract k2) -> Contract_repr.compare k1 k2 + | (Tx_rollup k1, Tx_rollup k2) -> Tx_rollup_repr.compare k1 k2 + (* This function is used by the Michelson interpreter to compare + addresses. It is of significant importance to remember that in + Michelson, address comparison is used to distinguish between + KT1 and tz1. As a consequence, we want to preserve that [tz1 < + KT1 < others], which the two following lines ensure. The + wildcards are therefore here for a reason, and should not be + modified when new constructors are added to [t]. *) + | (Contract _, _) -> -1 + | (_, Contract _) -> 1 end) -let to_b58check = function Contract k -> Contract_repr.to_b58check k +let to_b58check = function + | Contract k -> Contract_repr.to_b58check k + | Tx_rollup k -> Tx_rollup_repr.to_b58check k type error += Invalid_destination_b58check of string @@ -54,7 +66,10 @@ let () = let of_b58check s = match Contract_repr.of_b58check s with | Ok s -> Ok (Contract s) - | Error _ -> error (Invalid_destination_b58check s) + | Error _ -> ( + match Tx_rollup_repr.of_b58check s with + | Ok s -> Ok (Tx_rollup s) + | Error _ -> error (Invalid_destination_b58check s)) let encoding = let open Data_encoding in @@ -63,15 +78,24 @@ let encoding = ~title:"A destination of a transaction" ~description: "A destination notation compatible with the contract notation as given \ - to an RPC or inside scripts. Can be a base58 implicit contract hash or \ - a base58 originated contract hash." + to an RPC or inside scripts. Can be a base58 implicit contract hash, a \ + base58 originated contract hash, or a base58 originated transaction \ + rollup." @@ splitted ~binary: (union ~tag_size:`Uint8 (Contract_repr.cases - (function Contract x -> Some x) - (fun x -> Contract x))) + (function Contract x -> Some x | _ -> None) + (fun x -> Contract x) + @ [ + case + (Tag 2) + (Fixed.add_padding Tx_rollup_repr.encoding 1) + ~title:"Tx_rollup" + (function Tx_rollup k -> Some k | _ -> None) + (fun k -> Tx_rollup k); + ])) ~json: (conv to_b58check @@ -84,8 +108,12 @@ let encoding = string) let pp : Format.formatter -> t -> unit = - fun fmt -> function Contract k -> Contract_repr.pp fmt k + fun fmt -> function + | Contract k -> Contract_repr.pp fmt k + | Tx_rollup k -> Tx_rollup_repr.pp fmt k let in_memory_size = let open Cache_memory_helpers in - function Contract k -> h1w +! Contract_repr.in_memory_size k + function + | Contract k -> h1w +! Contract_repr.in_memory_size k + | Tx_rollup k -> h1w +! Tx_rollup_repr.in_memory_size k diff --git a/src/proto_alpha/lib_protocol/destination_repr.mli b/src/proto_alpha/lib_protocol/destination_repr.mli index 5ecb1d9671fe025e4dfcd73b0713bebdbc78c8f5..7b93a92aef8a5c1cdef45e4593574c7d72387024 100644 --- a/src/proto_alpha/lib_protocol/destination_repr.mli +++ b/src/proto_alpha/lib_protocol/destination_repr.mli @@ -41,7 +41,7 @@ remains compatible with {!Contract_repr.encoding}, for the introduction to this type to remain transparent from the existing tooling perspective. *) -type t = Contract of Contract_repr.t +type t = Contract of Contract_repr.t | Tx_rollup of Tx_rollup_repr.t include Compare.S with type t := t diff --git a/src/proto_alpha/lib_protocol/dune.inc b/src/proto_alpha/lib_protocol/dune.inc index 5f36b23d4a2b17d7ac7f279c52b2fc9df307932a..33065a5048ca60500d08ee011727d223a0774140 100644 --- a/src/proto_alpha/lib_protocol/dune.inc +++ b/src/proto_alpha/lib_protocol/dune.inc @@ -67,15 +67,17 @@ module CamlinternalFormatBasics = struct include CamlinternalFormatBasics end cache_memory_helpers.ml contract_repr.mli contract_repr.ml indexable.mli indexable.ml + entrypoint_repr.mli entrypoint_repr.ml tx_rollup_l2_address.mli tx_rollup_l2_address.ml tx_rollup_repr.mli tx_rollup_repr.ml tx_rollup_state_repr.mli tx_rollup_state_repr.ml tx_rollup_message_repr.mli tx_rollup_message_repr.ml tx_rollup_inbox_repr.mli tx_rollup_inbox_repr.ml + tx_rollup_commitments_repr.mli tx_rollup_commitments_repr.ml + tx_rollup_rejection_repr.mli tx_rollup_rejection_repr.ml roll_repr_legacy.mli roll_repr_legacy.ml vote_repr.mli vote_repr.ml block_header_repr.mli block_header_repr.ml - entrypoint_repr.mli entrypoint_repr.ml destination_repr.mli destination_repr.ml operation_repr.mli operation_repr.ml manager_repr.mli manager_repr.ml @@ -101,6 +103,7 @@ module CamlinternalFormatBasics = struct include CamlinternalFormatBasics end contract_manager_storage.mli contract_manager_storage.ml delegate_activation_storage.mli delegate_activation_storage.ml frozen_deposits_storage.mli frozen_deposits_storage.ml + tx_rollup_frozen_storage.mli tx_rollup_frozen_storage.ml stake_storage.mli stake_storage.ml contract_delegate_storage.mli contract_delegate_storage.ml sapling_storage.ml @@ -124,6 +127,8 @@ module CamlinternalFormatBasics = struct include CamlinternalFormatBasics end global_constants_storage.mli global_constants_storage.ml tx_rollup_state_storage.mli tx_rollup_state_storage.ml tx_rollup_inbox_storage.mli tx_rollup_inbox_storage.ml + tx_rollup_commitments_storage.mli tx_rollup_commitments_storage.ml + tx_rollup_offramp_storage.mli tx_rollup_offramp_storage.ml tx_rollup_storage.mli tx_rollup_storage.ml sc_rollup_storage.mli sc_rollup_storage.ml alpha_context.mli alpha_context.ml @@ -218,15 +223,17 @@ module CamlinternalFormatBasics = struct include CamlinternalFormatBasics end cache_memory_helpers.ml contract_repr.mli contract_repr.ml indexable.mli indexable.ml + entrypoint_repr.mli entrypoint_repr.ml tx_rollup_l2_address.mli tx_rollup_l2_address.ml tx_rollup_repr.mli tx_rollup_repr.ml tx_rollup_state_repr.mli tx_rollup_state_repr.ml tx_rollup_message_repr.mli tx_rollup_message_repr.ml tx_rollup_inbox_repr.mli tx_rollup_inbox_repr.ml + tx_rollup_commitments_repr.mli tx_rollup_commitments_repr.ml + tx_rollup_rejection_repr.mli tx_rollup_rejection_repr.ml roll_repr_legacy.mli roll_repr_legacy.ml vote_repr.mli vote_repr.ml block_header_repr.mli block_header_repr.ml - entrypoint_repr.mli entrypoint_repr.ml destination_repr.mli destination_repr.ml operation_repr.mli operation_repr.ml manager_repr.mli manager_repr.ml @@ -252,6 +259,7 @@ module CamlinternalFormatBasics = struct include CamlinternalFormatBasics end contract_manager_storage.mli contract_manager_storage.ml delegate_activation_storage.mli delegate_activation_storage.ml frozen_deposits_storage.mli frozen_deposits_storage.ml + tx_rollup_frozen_storage.mli tx_rollup_frozen_storage.ml stake_storage.mli stake_storage.ml contract_delegate_storage.mli contract_delegate_storage.ml sapling_storage.ml @@ -275,6 +283,8 @@ module CamlinternalFormatBasics = struct include CamlinternalFormatBasics end global_constants_storage.mli global_constants_storage.ml tx_rollup_state_storage.mli tx_rollup_state_storage.ml tx_rollup_inbox_storage.mli tx_rollup_inbox_storage.ml + tx_rollup_commitments_storage.mli tx_rollup_commitments_storage.ml + tx_rollup_offramp_storage.mli tx_rollup_offramp_storage.ml tx_rollup_storage.mli tx_rollup_storage.ml sc_rollup_storage.mli sc_rollup_storage.ml alpha_context.mli alpha_context.ml @@ -369,15 +379,17 @@ module CamlinternalFormatBasics = struct include CamlinternalFormatBasics end cache_memory_helpers.ml contract_repr.mli contract_repr.ml indexable.mli indexable.ml + entrypoint_repr.mli entrypoint_repr.ml tx_rollup_l2_address.mli tx_rollup_l2_address.ml tx_rollup_repr.mli tx_rollup_repr.ml tx_rollup_state_repr.mli tx_rollup_state_repr.ml tx_rollup_message_repr.mli tx_rollup_message_repr.ml tx_rollup_inbox_repr.mli tx_rollup_inbox_repr.ml + tx_rollup_commitments_repr.mli tx_rollup_commitments_repr.ml + tx_rollup_rejection_repr.mli tx_rollup_rejection_repr.ml roll_repr_legacy.mli roll_repr_legacy.ml vote_repr.mli vote_repr.ml block_header_repr.mli block_header_repr.ml - entrypoint_repr.mli entrypoint_repr.ml destination_repr.mli destination_repr.ml operation_repr.mli operation_repr.ml manager_repr.mli manager_repr.ml @@ -403,6 +415,7 @@ module CamlinternalFormatBasics = struct include CamlinternalFormatBasics end contract_manager_storage.mli contract_manager_storage.ml delegate_activation_storage.mli delegate_activation_storage.ml frozen_deposits_storage.mli frozen_deposits_storage.ml + tx_rollup_frozen_storage.mli tx_rollup_frozen_storage.ml stake_storage.mli stake_storage.ml contract_delegate_storage.mli contract_delegate_storage.ml sapling_storage.ml @@ -426,6 +439,8 @@ module CamlinternalFormatBasics = struct include CamlinternalFormatBasics end global_constants_storage.mli global_constants_storage.ml tx_rollup_state_storage.mli tx_rollup_state_storage.ml tx_rollup_inbox_storage.mli tx_rollup_inbox_storage.ml + tx_rollup_commitments_storage.mli tx_rollup_commitments_storage.ml + tx_rollup_offramp_storage.mli tx_rollup_offramp_storage.ml tx_rollup_storage.mli tx_rollup_storage.ml sc_rollup_storage.mli sc_rollup_storage.ml alpha_context.mli alpha_context.ml @@ -542,15 +557,17 @@ include Tezos_raw_protocol_alpha.Main Cache_memory_helpers Contract_repr Indexable + Entrypoint_repr Tx_rollup_l2_address Tx_rollup_repr Tx_rollup_state_repr Tx_rollup_message_repr Tx_rollup_inbox_repr + Tx_rollup_commitments_repr + Tx_rollup_rejection_repr Roll_repr_legacy Vote_repr Block_header_repr - Entrypoint_repr Destination_repr Operation_repr Manager_repr @@ -576,6 +593,7 @@ include Tezos_raw_protocol_alpha.Main Contract_manager_storage Delegate_activation_storage Frozen_deposits_storage + Tx_rollup_frozen_storage Stake_storage Contract_delegate_storage Sapling_storage @@ -599,6 +617,8 @@ include Tezos_raw_protocol_alpha.Main Global_constants_storage Tx_rollup_state_storage Tx_rollup_inbox_storage + Tx_rollup_commitments_storage + Tx_rollup_offramp_storage Tx_rollup_storage Sc_rollup_storage Alpha_context @@ -734,15 +754,17 @@ include Tezos_raw_protocol_alpha.Main cache_memory_helpers.ml contract_repr.mli contract_repr.ml indexable.mli indexable.ml + entrypoint_repr.mli entrypoint_repr.ml tx_rollup_l2_address.mli tx_rollup_l2_address.ml tx_rollup_repr.mli tx_rollup_repr.ml tx_rollup_state_repr.mli tx_rollup_state_repr.ml tx_rollup_message_repr.mli tx_rollup_message_repr.ml tx_rollup_inbox_repr.mli tx_rollup_inbox_repr.ml + tx_rollup_commitments_repr.mli tx_rollup_commitments_repr.ml + tx_rollup_rejection_repr.mli tx_rollup_rejection_repr.ml roll_repr_legacy.mli roll_repr_legacy.ml vote_repr.mli vote_repr.ml block_header_repr.mli block_header_repr.ml - entrypoint_repr.mli entrypoint_repr.ml destination_repr.mli destination_repr.ml operation_repr.mli operation_repr.ml manager_repr.mli manager_repr.ml @@ -768,6 +790,7 @@ include Tezos_raw_protocol_alpha.Main contract_manager_storage.mli contract_manager_storage.ml delegate_activation_storage.mli delegate_activation_storage.ml frozen_deposits_storage.mli frozen_deposits_storage.ml + tx_rollup_frozen_storage.mli tx_rollup_frozen_storage.ml stake_storage.mli stake_storage.ml contract_delegate_storage.mli contract_delegate_storage.ml sapling_storage.ml @@ -791,6 +814,8 @@ include Tezos_raw_protocol_alpha.Main global_constants_storage.mli global_constants_storage.ml tx_rollup_state_storage.mli tx_rollup_state_storage.ml tx_rollup_inbox_storage.mli tx_rollup_inbox_storage.ml + tx_rollup_commitments_storage.mli tx_rollup_commitments_storage.ml + tx_rollup_offramp_storage.mli tx_rollup_offramp_storage.ml tx_rollup_storage.mli tx_rollup_storage.ml sc_rollup_storage.mli sc_rollup_storage.ml alpha_context.mli alpha_context.ml diff --git a/src/proto_alpha/lib_protocol/michelson_v1_gas.ml b/src/proto_alpha/lib_protocol/michelson_v1_gas.ml index fec8bcee756298a4289590ac93058cc8c43496d9..5d9dc416a6c0e425bf83d32a8709987c63bf7f98 100644 --- a/src/proto_alpha/lib_protocol/michelson_v1_gas.ml +++ b/src/proto_alpha/lib_protocol/michelson_v1_gas.ml @@ -1358,6 +1358,10 @@ module Cost_of = struct let sz = Signature.Public_key_hash.size + entrypoint_size in atomic_step_cost (cost_N_ICompare sz sz) + (** TODO: https://gitlab.com/tezos/tezos/-/issues/2340 + Refine the gas model *) + let compare_tx_rollup_l2_address = atomic_step_cost (cost_N_ICompare 48 48) + let compare_chain_id = atomic_step_cost (S.safe_int 30) (* Defunctionalized CPS *) @@ -1387,6 +1391,8 @@ module Cost_of = struct | Timestamp_key _ -> (apply [@tailcall]) Gas.(acc +@ compare_timestamp x y) k | Address_key _ -> (apply [@tailcall]) Gas.(acc +@ compare_address) k + | Tx_rollup_l2_address_key _ -> + (apply [@tailcall]) Gas.(acc +@ compare_tx_rollup_l2_address) k | Chain_id_key _ -> (apply [@tailcall]) Gas.(acc +@ compare_chain_id) k | Pair_key (tl, tr, _) -> (* Reasonable over-approximation of the cost of lexicographic comparison. *) @@ -1686,6 +1692,10 @@ module Cost_of = struct (* Reasonable estimate. *) let contract = Gas.(S.safe_int 2 *@ public_key_readable) + (** TODO: https://gitlab.com/tezos/tezos/-/issues/2340 + Refine the gas model *) + let tx_rollup_l2_address = bls12_381_g1 + (* Balance stored at /contracts/index/hash/balance, on 64 bits *) let contract_exists = Gas.cost_of_repr @@ Storage_costs.read_access ~path_length:4 ~read_bytes:8 @@ -1796,6 +1806,10 @@ module Cost_of = struct (* Reasonable estimate. *) let contract = Gas.(S.safe_int 2 *@ public_key_readable) + (** TODO: https://gitlab.com/tezos/tezos/-/issues/2340 + Refine the gas model *) + let tx_rollup_l2_address = bls12_381_g1 + (* Reuse 006 costs. *) let operation bytes = Script.bytes_node_cost bytes diff --git a/src/proto_alpha/lib_protocol/michelson_v1_gas.mli b/src/proto_alpha/lib_protocol/michelson_v1_gas.mli index bc831637509877b993c678b86f8e7195e5795cd4..8830557f6fe928c1a9fe6bb380535723d16d54d0 100644 --- a/src/proto_alpha/lib_protocol/michelson_v1_gas.mli +++ b/src/proto_alpha/lib_protocol/michelson_v1_gas.mli @@ -443,6 +443,8 @@ module Cost_of : sig val contract : Gas.cost + val tx_rollup_l2_address : Gas.cost + val contract_exists : Gas.cost val proof_argument : int -> Gas.cost @@ -495,6 +497,8 @@ module Cost_of : sig val contract : Gas.cost + val tx_rollup_l2_address : Gas.cost + val operation : bytes -> Gas.cost val sapling_transaction : Sapling.transaction -> Gas.cost diff --git a/src/proto_alpha/lib_protocol/michelson_v1_primitives.ml b/src/proto_alpha/lib_protocol/michelson_v1_primitives.ml index c1434b14ec1462e2a9a8fc17e0d9a66ddfe7babc..f6c81c88f3dea415dfb277aff2cbc01557e4d86b 100644 --- a/src/proto_alpha/lib_protocol/michelson_v1_primitives.ml +++ b/src/proto_alpha/lib_protocol/michelson_v1_primitives.ml @@ -172,6 +172,7 @@ type prim = | T_unit | T_operation | T_address + | T_tx_rollup_l2_address | T_sapling_transaction | T_sapling_state | T_chain_id @@ -215,12 +216,12 @@ let namespace = function | I_SWAP | I_TICKET | I_TOTAL_VOTING_POWER | I_TRANSFER_TOKENS | I_UNIT | I_UNPACK | I_UNPAIR | I_UPDATE | I_VOTING_POWER | I_XOR | I_OPEN_CHEST -> Instr_namespace - | T_address | T_big_map | T_bool | T_bytes | T_chain_id | T_contract | T_int - | T_key | T_key_hash | T_lambda | T_list | T_map | T_mutez | T_nat | T_never - | T_operation | T_option | T_or | T_pair | T_sapling_state - | T_sapling_transaction | T_set | T_signature | T_string | T_timestamp - | T_unit | T_bls12_381_fr | T_bls12_381_g1 | T_bls12_381_g2 | T_ticket - | T_chest_key | T_chest -> + | T_address | T_tx_rollup_l2_address | T_big_map | T_bool | T_bytes + | T_chain_id | T_contract | T_int | T_key | T_key_hash | T_lambda | T_list + | T_map | T_mutez | T_nat | T_never | T_operation | T_option | T_or | T_pair + | T_sapling_state | T_sapling_transaction | T_set | T_signature | T_string + | T_timestamp | T_unit | T_bls12_381_fr | T_bls12_381_g1 | T_bls12_381_g2 + | T_ticket | T_chest_key | T_chest -> Type_namespace | H_constant -> Constant_hash_namespace @@ -376,6 +377,7 @@ let string_of_prim = function | T_unit -> "unit" | T_operation -> "operation" | T_address -> "address" + | T_tx_rollup_l2_address -> "tx_rollup_l2_address" | T_sapling_state -> "sapling_state" | T_sapling_transaction -> "sapling_transaction" | T_chain_id -> "chain_id" @@ -526,6 +528,7 @@ let prim_of_string = function | "unit" -> ok T_unit | "operation" -> ok T_operation | "address" -> ok T_address + | "tx_rollup_l2_address" -> ok T_tx_rollup_l2_address | "sapling_state" -> ok T_sapling_state | "sapling_transaction" -> ok T_sapling_transaction | "chain_id" -> ok T_chain_id @@ -748,6 +751,8 @@ let prim_encoding = ("constant", H_constant); (* Alpha_012 addition *) ("SUB_MUTEZ", I_SUB_MUTEZ); + (* Alpha_013 addition *) + ("tx_rollup_l2_address", T_tx_rollup_l2_address); (* New instructions must be added here, for backward compatibility of the encoding. *) (* Keep the comment above at the end of the list *) ] diff --git a/src/proto_alpha/lib_protocol/michelson_v1_primitives.mli b/src/proto_alpha/lib_protocol/michelson_v1_primitives.mli index 3c2a65db73dd45007b72c0b7b90821db4b001c80..8b8e5baf39c345788f3613b1a2f8b8029e334207 100644 --- a/src/proto_alpha/lib_protocol/michelson_v1_primitives.mli +++ b/src/proto_alpha/lib_protocol/michelson_v1_primitives.mli @@ -43,7 +43,7 @@ type error += a few extra atom types for strings and numbers. This variant represents the values the [Prim] atoms in the Michelson subset of Micheline. Other types (such as ['a Micheline.canonical]) are - frequently parameterized by this type. This gives us a strongly-typed + frequently parameterized by this type. This gives us a strongly-typed subset of Micheline while keeping the set of primitives independent from the definition of Micheline for easier changes. *) @@ -185,6 +185,7 @@ type prim = | T_unit | T_operation | T_address + | T_tx_rollup_l2_address | T_sapling_transaction | T_sapling_state | T_chain_id diff --git a/src/proto_alpha/lib_protocol/operation_repr.ml b/src/proto_alpha/lib_protocol/operation_repr.ml index 24b882ddbcf6c94324ae920914e38f87f3a1d1db..f9bda8ee9329dec448f98f4e27a9d5328a58716c 100644 --- a/src/proto_alpha/lib_protocol/operation_repr.ml +++ b/src/proto_alpha/lib_protocol/operation_repr.ml @@ -75,6 +75,14 @@ module Kind = struct type tx_rollup_submit_batch = Tx_rollup_submit_batch_kind + type tx_rollup_commit = Tx_rollup_commit_kind + + type tx_rollup_return_bond = Tx_rollup_return_bond_kind + + type tx_rollup_rejection = Tx_rollup_rejection_kind + + type tx_rollup_prerejection = Tx_rollup_prerejection_kind + type sc_rollup_originate = Sc_rollup_originate_kind type sc_rollup_add_messages = Sc_rollup_add_messages_kind @@ -88,6 +96,10 @@ module Kind = struct | Set_deposits_limit_manager_kind : set_deposits_limit manager | Tx_rollup_origination_manager_kind : tx_rollup_origination manager | Tx_rollup_submit_batch_manager_kind : tx_rollup_submit_batch manager + | Tx_rollup_commit_manager_kind : tx_rollup_commit manager + | Tx_rollup_return_bond_manager_kind : tx_rollup_return_bond manager + | Tx_rollup_rejection_manager_kind : tx_rollup_rejection manager + | Tx_rollup_prerejection_manager_kind : tx_rollup_prerejection manager | Sc_rollup_originate_manager_kind : sc_rollup_originate manager | Sc_rollup_add_messages_manager_kind : sc_rollup_add_messages manager end @@ -273,6 +285,28 @@ and _ manager_operation = content : string; } -> Kind.tx_rollup_submit_batch manager_operation + | Tx_rollup_commit : { + rollup : Tx_rollup_repr.t; + commitment : Tx_rollup_commitments_repr.Commitment.t; + } + -> Kind.tx_rollup_commit manager_operation + | Tx_rollup_return_bond : { + rollup : Tx_rollup_repr.t; + } + -> Kind.tx_rollup_return_bond manager_operation + | Tx_rollup_rejection : { + rollup : Tx_rollup_repr.t; + level : Raw_level_repr.t; + hash : Tx_rollup_commitments_repr.Commitment_hash.t; + batch_index : int; + batch : Tx_rollup_message_repr.t; + nonce : int64; + } + -> Kind.tx_rollup_rejection manager_operation + | Tx_rollup_prerejection : { + hash : Tx_rollup_rejection_repr.Rejection_hash.t; + } + -> Kind.tx_rollup_prerejection manager_operation | Sc_rollup_originate : { kind : Sc_rollup_repr.Kind.t; boot_sector : Sc_rollup_repr.PVM.boot_sector; @@ -296,6 +330,10 @@ let manager_kind : type kind. kind manager_operation -> kind Kind.manager = | Set_deposits_limit _ -> Kind.Set_deposits_limit_manager_kind | Tx_rollup_origination -> Kind.Tx_rollup_origination_manager_kind | Tx_rollup_submit_batch _ -> Kind.Tx_rollup_submit_batch_manager_kind + | Tx_rollup_commit _ -> Kind.Tx_rollup_commit_manager_kind + | Tx_rollup_return_bond _ -> Kind.Tx_rollup_return_bond_manager_kind + | Tx_rollup_rejection _ -> Kind.Tx_rollup_rejection_manager_kind + | Tx_rollup_prerejection _ -> Kind.Tx_rollup_prerejection_manager_kind | Sc_rollup_originate _ -> Kind.Sc_rollup_originate_manager_kind | Sc_rollup_add_messages _ -> Kind.Sc_rollup_add_messages_manager_kind @@ -543,6 +581,79 @@ module Encoding = struct Tx_rollup_submit_batch {tx_rollup; content}); } + let[@coq_axiom_with_reason "gadt"] tx_rollup_commit_case = + MCase + { + tag = tx_rollup_operation_tag_offset + 2; + name = "tx_rollup_commit"; + encoding = + obj2 + (req "rollup" Tx_rollup_repr.encoding) + (req "commitment" Tx_rollup_commitments_repr.Commitment.encoding); + select = + (function + | Manager (Tx_rollup_commit _ as op) -> Some op | _ -> None); + proj = + (function + | Tx_rollup_commit {rollup; commitment} -> (rollup, commitment)); + inj = + (fun (rollup, commitment) -> Tx_rollup_commit {rollup; commitment}); + } + + let[@coq_axiom_with_reason "gadt"] tx_rollup_return_bond_case = + MCase + { + tag = tx_rollup_operation_tag_offset + 3; + name = "tx_rollup_return_bond"; + encoding = obj1 (req "rollup" Tx_rollup_repr.encoding); + select = + (function + | Manager (Tx_rollup_return_bond _ as op) -> Some op | _ -> None); + proj = (function Tx_rollup_return_bond {rollup} -> rollup); + inj = (fun rollup -> Tx_rollup_return_bond {rollup}); + } + + let[@coq_axiom_with_reason "gadt"] tx_rollup_rejection_case = + MCase + { + tag = tx_rollup_operation_tag_offset + 4; + name = "tx_rollup_rejection"; + encoding = + obj6 + (req "rollup" Tx_rollup_repr.encoding) + (req "level" Raw_level_repr.encoding) + (req "hash" Tx_rollup_commitments_repr.Commitment_hash.encoding) + (req "batch_index" int31) + (req "batch" Tx_rollup_message_repr.encoding) + (req "nonce" int64); + select = + (function + | Manager (Tx_rollup_rejection _ as op) -> Some op | _ -> None); + proj = + (function + | Tx_rollup_rejection + {rollup; level; hash; batch_index; batch; nonce} -> + (rollup, level, hash, batch_index, batch, nonce)); + inj = + (fun (rollup, level, hash, batch_index, batch, nonce) -> + Tx_rollup_rejection + {rollup; level; hash; batch_index; batch; nonce}); + } + + let[@coq_axiom_with_reason "gadt"] tx_rollup_prerejection_case = + MCase + { + tag = tx_rollup_operation_tag_offset + 5; + name = "tx_rollup_prerejection"; + encoding = + obj1 (req "hash" Tx_rollup_rejection_repr.Rejection_hash.encoding); + select = + (function + | Manager (Tx_rollup_prerejection _ as op) -> Some op | _ -> None); + proj = (function Tx_rollup_prerejection {hash} -> hash); + inj = (fun hash -> Tx_rollup_prerejection {hash}); + } + let[@coq_axiom_with_reason "gadt"] sc_rollup_originate_case = MCase { @@ -603,6 +714,10 @@ module Encoding = struct make set_deposits_limit_case; make tx_rollup_origination_case; make tx_rollup_submit_batch_case; + make tx_rollup_commit_case; + make tx_rollup_return_bond_case; + make tx_rollup_rejection_case; + make tx_rollup_prerejection_case; make sc_rollup_originate_case; make sc_rollup_add_messages_case; ] @@ -913,6 +1028,26 @@ module Encoding = struct (tx_rollup_operation_tag_offset + 1) Manager_operations.tx_rollup_submit_batch_case + let tx_rollup_commit_case = + make_manager_case + (tx_rollup_operation_tag_offset + 2) + Manager_operations.tx_rollup_commit_case + + let tx_rollup_return_bond_case = + make_manager_case + (tx_rollup_operation_tag_offset + 3) + Manager_operations.tx_rollup_return_bond_case + + let tx_rollup_rejection_case = + make_manager_case + (tx_rollup_operation_tag_offset + 4) + Manager_operations.tx_rollup_rejection_case + + let tx_rollup_prerejection_case = + make_manager_case + (tx_rollup_operation_tag_offset + 5) + Manager_operations.tx_rollup_prerejection_case + let sc_rollup_originate_case = make_manager_case sc_rollup_operation_origination_tag @@ -953,6 +1088,10 @@ module Encoding = struct make register_global_constant_case; make tx_rollup_origination_case; make tx_rollup_submit_batch_case; + make tx_rollup_commit_case; + make tx_rollup_return_bond_case; + make tx_rollup_rejection_case; + make tx_rollup_prerejection_case; make sc_rollup_originate_case; make sc_rollup_add_messages_case; ] @@ -1158,6 +1297,14 @@ let equal_manager_operation_kind : | (Tx_rollup_origination, _) -> None | (Tx_rollup_submit_batch _, Tx_rollup_submit_batch _) -> Some Eq | (Tx_rollup_submit_batch _, _) -> None + | (Tx_rollup_commit _, Tx_rollup_commit _) -> Some Eq + | (Tx_rollup_commit _, _) -> None + | (Tx_rollup_return_bond _, Tx_rollup_return_bond _) -> Some Eq + | (Tx_rollup_return_bond _, _) -> None + | (Tx_rollup_rejection _, Tx_rollup_rejection _) -> Some Eq + | (Tx_rollup_rejection _, _) -> None + | (Tx_rollup_prerejection _, Tx_rollup_prerejection _) -> Some Eq + | (Tx_rollup_prerejection _, _) -> None | (Sc_rollup_originate _, Sc_rollup_originate _) -> Some Eq | (Sc_rollup_originate _, _) -> None | (Sc_rollup_add_messages _, Sc_rollup_add_messages _) -> Some Eq @@ -1270,6 +1417,18 @@ let internal_manager_operation_size (type a) (op : a manager_operation) = | Tx_rollup_submit_batch _ -> (* Tx_rollup_submit_batch operation can’t occur as internal operations *) assert false + | Tx_rollup_commit _ -> + (* Tx_rollup_commit operation can’t occur as internal operations *) + assert false + | Tx_rollup_return_bond _ -> + (* Tx_rollup_return_bond operation can’t occur as internal operations *) + assert false + | Tx_rollup_rejection _ -> + (* Tx_rollup_rejection operation can’t occur as internal operations *) + assert false + | Tx_rollup_prerejection _ -> + (* Tx_rollup_prerejection operation can’t occur as internal operations *) + assert false let packed_internal_operation_in_memory_size : packed_internal_operation -> nodes_and_size = function diff --git a/src/proto_alpha/lib_protocol/operation_repr.mli b/src/proto_alpha/lib_protocol/operation_repr.mli index 022990d2e9774868b9fbd852d1824122a7a3eff2..8a33571d61629c63b0b66fba996af853a70c1f6c 100644 --- a/src/proto_alpha/lib_protocol/operation_repr.mli +++ b/src/proto_alpha/lib_protocol/operation_repr.mli @@ -101,6 +101,14 @@ module Kind : sig type tx_rollup_submit_batch = Tx_rollup_submit_batch_kind + type tx_rollup_commit = Tx_rollup_commit_kind + + type tx_rollup_return_bond = Tx_rollup_return_bond_kind + + type tx_rollup_rejection = Tx_rollup_rejection_kind + + type tx_rollup_prerejection = Tx_rollup_prerejection_kind + type sc_rollup_originate = Sc_rollup_originate_kind type sc_rollup_add_messages = Sc_rollup_add_messages_kind @@ -114,6 +122,10 @@ module Kind : sig | Set_deposits_limit_manager_kind : set_deposits_limit manager | Tx_rollup_origination_manager_kind : tx_rollup_origination manager | Tx_rollup_submit_batch_manager_kind : tx_rollup_submit_batch manager + | Tx_rollup_commit_manager_kind : tx_rollup_commit manager + | Tx_rollup_return_bond_manager_kind : tx_rollup_return_bond manager + | Tx_rollup_rejection_manager_kind : tx_rollup_rejection manager + | Tx_rollup_prerejection_manager_kind : tx_rollup_prerejection manager | Sc_rollup_originate_manager_kind : sc_rollup_originate manager | Sc_rollup_add_messages_manager_kind : sc_rollup_add_messages manager end @@ -252,6 +264,28 @@ and _ manager_operation = content : string; } -> Kind.tx_rollup_submit_batch manager_operation + | Tx_rollup_commit : { + rollup : Tx_rollup_repr.t; + commitment : Tx_rollup_commitments_repr.Commitment.t; + } + -> Kind.tx_rollup_commit manager_operation + | Tx_rollup_return_bond : { + rollup : Tx_rollup_repr.t; + } + -> Kind.tx_rollup_return_bond manager_operation + | Tx_rollup_rejection : { + rollup : Tx_rollup_repr.t; + level : Raw_level_repr.t; + hash : Tx_rollup_commitments_repr.Commitment_hash.t; + batch_index : int; + batch : Tx_rollup_message_repr.t; + nonce : int64; + } + -> Kind.tx_rollup_rejection manager_operation + | Tx_rollup_prerejection : { + hash : Tx_rollup_rejection_repr.Rejection_hash.t; + } + -> Kind.tx_rollup_prerejection manager_operation | Sc_rollup_originate : { kind : Sc_rollup_repr.Kind.t; boot_sector : Sc_rollup_repr.PVM.boot_sector; @@ -386,6 +420,15 @@ module Encoding : sig val tx_rollup_submit_batch_case : Kind.tx_rollup_submit_batch Kind.manager case + val tx_rollup_commit_case : Kind.tx_rollup_commit Kind.manager case + + val tx_rollup_return_bond_case : Kind.tx_rollup_return_bond Kind.manager case + + val tx_rollup_rejection_case : Kind.tx_rollup_rejection Kind.manager case + + val tx_rollup_prerejection_case : + Kind.tx_rollup_prerejection Kind.manager case + val sc_rollup_originate_case : Kind.sc_rollup_originate Kind.manager case val sc_rollup_add_messages_case : @@ -419,6 +462,14 @@ module Encoding : sig val tx_rollup_submit_batch_case : Kind.tx_rollup_submit_batch case + val tx_rollup_commit_case : Kind.tx_rollup_commit case + + val tx_rollup_return_bond_case : Kind.tx_rollup_return_bond case + + val tx_rollup_rejection_case : Kind.tx_rollup_rejection case + + val tx_rollup_prerejection_case : Kind.tx_rollup_prerejection case + val sc_rollup_originate_case : Kind.sc_rollup_originate case val sc_rollup_add_messages_case : Kind.sc_rollup_add_messages case diff --git a/src/proto_alpha/lib_protocol/raw_context.ml b/src/proto_alpha/lib_protocol/raw_context.ml index 0ea6b281462c666f9efa41805e485a8e598b83cb..a46970010666d0ac21d3762e1733ac4be929be2f 100644 --- a/src/proto_alpha/lib_protocol/raw_context.ml +++ b/src/proto_alpha/lib_protocol/raw_context.ml @@ -881,6 +881,7 @@ let prepare_first_block ~level ~timestamp ctxt = tx_rollup_origination_size = 60_000; tx_rollup_hard_size_limit_per_inbox = 100_000; tx_rollup_hard_size_limit_per_message = 5_000; + tx_rollup_commitment_bond = Tez_repr.of_mutez_exn 10_000_000_000L; sc_rollup_enable = false; (* The following value is chosen to prevent spam. *) sc_rollup_origination_size = 6_314; diff --git a/src/proto_alpha/lib_protocol/receipt_repr.ml b/src/proto_alpha/lib_protocol/receipt_repr.ml index eeb6ab22a70cebb6d44e404d0bff99ebc36ef950..b4083deee3f5f35049cf892f7a57ff3068a86ab3 100644 --- a/src/proto_alpha/lib_protocol/receipt_repr.ml +++ b/src/proto_alpha/lib_protocol/receipt_repr.ml @@ -46,6 +46,7 @@ type balance = | Invoice | Initial_commitments | Minted + | Rollup_bond let balance_encoding = let open Data_encoding in @@ -235,6 +236,14 @@ let balance_encoding = (req "category" (constant "minted"))) (function Minted -> Some ((), ()) | _ -> None) (fun ((), ()) -> Minted); + case + (Tag 21) + ~title:"Rollup_bond" + (obj2 + (req "kind" (constant "rollup_bond")) + (req "category" (constant "rollup_bond"))) + (function Rollup_bond -> Some ((), ()) | _ -> None) + (fun ((), ()) -> Rollup_bond); ] let is_not_zero c = not (Compare.Int.equal c 0) @@ -286,6 +295,7 @@ let compare_balance ba bb = | Invoice -> 18 | Initial_commitments -> 19 | Minted -> 20 + | Rollup_bond -> 21 (* don't forget to add parameterized cases in the first part of the function *) in Compare.Int.compare (index ba) (index bb) diff --git a/src/proto_alpha/lib_protocol/receipt_repr.mli b/src/proto_alpha/lib_protocol/receipt_repr.mli index 7457de8aefd68bc8178337eea5eb21b257ad7e67..4a026e806bf65cf07fe00af772f86cbf7c41325a 100644 --- a/src/proto_alpha/lib_protocol/receipt_repr.mli +++ b/src/proto_alpha/lib_protocol/receipt_repr.mli @@ -47,6 +47,7 @@ type balance = | Invoice | Initial_commitments | Minted + | Rollup_bond (** Compares two balances. *) val compare_balance : balance -> balance -> int diff --git a/src/proto_alpha/lib_protocol/script_comparable.ml b/src/proto_alpha/lib_protocol/script_comparable.ml index ee5755f5704bb75041b897cf29dd9f723e493001..c854428edd5baf5e19deb1e0af7be457215f7fee 100644 --- a/src/proto_alpha/lib_protocol/script_comparable.ml +++ b/src/proto_alpha/lib_protocol/script_comparable.ml @@ -34,6 +34,8 @@ let compare_address {destination = destination1; entrypoint = entrypoint1} if Compare.Int.(lres = 0) then Entrypoint.compare entrypoint1 entrypoint2 else lres +let compare_tx_rollup_l2_address = Tx_rollup_l2_address.Indexable.compare + type compare_comparable_cont = | Compare_comparable : 'a comparable_ty * 'a * 'a * compare_comparable_cont @@ -61,6 +63,8 @@ let compare_comparable : type a. a comparable_ty -> a -> a -> int = | (Timestamp_key _, x, y) -> (apply [@tailcall]) (Script_timestamp.compare x y) k | (Address_key _, x, y) -> (apply [@tailcall]) (compare_address x y) k + | (Tx_rollup_l2_address_key _, x, y) -> + (apply [@tailcall]) (compare_tx_rollup_l2_address x y) k | (Bytes_key _, x, y) -> (apply [@tailcall]) (Compare.Bytes.compare x y) k | (Chain_id_key _, x, y) -> (apply [@tailcall]) (Script_chain_id.compare x y) k diff --git a/src/proto_alpha/lib_protocol/script_comparable.mli b/src/proto_alpha/lib_protocol/script_comparable.mli index 8f489511625a709dca26feb925f75b0672bfc2c5..70c1f809d41f82e41df1b7582b235b30a2f43ed4 100644 --- a/src/proto_alpha/lib_protocol/script_comparable.mli +++ b/src/proto_alpha/lib_protocol/script_comparable.mli @@ -27,3 +27,8 @@ val compare_comparable : 'a Script_typed_ir.comparable_ty -> 'a -> 'a -> int val compare_address : Script_typed_ir.address -> Script_typed_ir.address -> int + +val compare_tx_rollup_l2_address : + Script_typed_ir.tx_rollup_l2_address -> + Script_typed_ir.tx_rollup_l2_address -> + int diff --git a/src/proto_alpha/lib_protocol/script_interpreter.ml b/src/proto_alpha/lib_protocol/script_interpreter.ml index 13db0be58c6798654637411024afdaddd22fe38a..1896aaef28578afd5a76a7b3631276c8f85e80ec 100644 --- a/src/proto_alpha/lib_protocol/script_interpreter.ml +++ b/src/proto_alpha/lib_protocol/script_interpreter.ml @@ -1028,13 +1028,13 @@ and step : type a s b t r f. (a, s, b, t, r, f) step_type = let (addr, stack) = stack in let c = addr.destination in let ctxt = update_context gas ctxt in + let return_none ctxt = + let (gas, ctxt) = local_gas_counter_and_outdated_context ctxt in + (step [@ocaml.tailcall]) (ctxt, sc) gas k ks None stack + in match c with | Contract c -> ( Contract.get_script ctxt c >>=? fun (ctxt, script_opt) -> - let return_none ctxt = - let (gas, ctxt) = local_gas_counter_and_outdated_context ctxt in - (step [@ocaml.tailcall]) (ctxt, sc) gas k ks None stack - in match script_opt with | None -> (return_none [@ocaml.tailcall]) ctxt | Some script -> ( @@ -1125,7 +1125,8 @@ and step : type a s b t r f. (a, s, b, t, r, f) step_type = kinstr (KView_exit (sc, KReturn (stack, ks))) (input, storage) - (EmptyCell, EmptyCell))))))) + (EmptyCell, EmptyCell)))))) + | Tx_rollup _ -> (return_none [@ocaml.tailcall]) ctxt) | ICreate_contract { storage_type; diff --git a/src/proto_alpha/lib_protocol/script_interpreter_defs.ml b/src/proto_alpha/lib_protocol/script_interpreter_defs.ml index 1894cc1a5efe24fbdc9ae54cb27a43e297bc4f90..569a354766cffcaab3110bcece51422fc60e5f50 100644 --- a/src/proto_alpha/lib_protocol/script_interpreter_defs.ml +++ b/src/proto_alpha/lib_protocol/script_interpreter_defs.ml @@ -493,6 +493,37 @@ let apply ctxt gas capture_ty capture lam = let (gas, ctxt) = local_gas_counter_and_outdated_context ctxt in return (lam', ctxt, gas) +(** [craft_transfer_parameters ctxt tp p] reorganizes, if need be, the + parameters submitted by the interpreter to prepare them for the + [Transaction] operation. *) +let craft_transfer_parameters ctxt tp p : Destination.t -> _ tzresult = function + | Contract _ -> ok (p, ctxt) + (* The entrypoints of a transaction rollup are polymorphic wrt. the + tickets it can process. However, two Michelson values can have + the same Micheline representation, but different types. What + this means is that when we start the execution of a transaction + rollup, the type of its argument is lost if we just give it the + values provided by the Michelson script. + + To address this issue, we instrument a transfer to a transaction + rollup to inject the exact type of the entrypoint as used by + the smart contract. This allows the transaction rollup to extract + the type of the ticket. *) + | Tx_rollup _ -> + let open Micheline in + (* The entrypoint type is [Pair (Ticket a) tx_rollup_l2_address]. + We are only interested in the ticket type. *) + let extract_ticket_type = function + | Prim (_, T_pair, [Prim (_, T_ticket, [ty], _); _], _) -> ty + | _ -> + (* The implementation of the [CONTRACT] instruction + enforces that this cannot happen. *) + assert false + in + Script_ir_translator.unparse_ty ~loc:dummy_location ctxt tp + >|? fun (ty, ctxt) -> + (Seq (dummy_location, [p; extract_ticket_type ty]), ctxt) + (* [transfer (ctxt, sc) gas tez tp p destination entrypoint] creates an operation that transfers an amount of [tez] to a contract determined by [(destination, entrypoint)] @@ -512,6 +543,7 @@ let transfer (ctxt, sc) gas amount tp p destination entrypoint = >>=? fun (p, lazy_storage_diff, ctxt) -> unparse_data ctxt Optimized tp p >>=? fun (p, ctxt) -> Gas.consume ctxt (Script.strip_locations_cost p) >>?= fun ctxt -> + craft_transfer_parameters ctxt tp p destination >>?= fun (p, ctxt) -> let operation = Transaction { diff --git a/src/proto_alpha/lib_protocol/script_ir_translator.ml b/src/proto_alpha/lib_protocol/script_ir_translator.ml index f6806f9b93f9d075991aa060679e663b14207f91..009b0c9ac6f387837b27be76778b7d9d5fc32b78 100644 --- a/src/proto_alpha/lib_protocol/script_ir_translator.ml +++ b/src/proto_alpha/lib_protocol/script_ir_translator.ml @@ -171,6 +171,7 @@ let rec ty_of_comparable_ty : type a. a comparable_ty -> a ty = function | Key_key tname -> Key_t tname | Timestamp_key tname -> Timestamp_t tname | Address_key tname -> Address_t tname + | Tx_rollup_l2_address_key tname -> Tx_rollup_l2_address_t tname | Chain_id_key tname -> Chain_id_t tname | Pair_key (l, r, tname) -> Pair_t (ty_of_comparable_ty l, ty_of_comparable_ty r, tname) @@ -200,6 +201,7 @@ let rec unparse_comparable_ty_uncarbonated : | Key_key _meta -> Prim (loc, T_key, [], []) | Timestamp_key _meta -> Prim (loc, T_timestamp, [], []) | Address_key _meta -> Prim (loc, T_address, [], []) + | Tx_rollup_l2_address_key _meta -> Prim (loc, T_tx_rollup_l2_address, [], []) | Chain_id_key _meta -> Prim (loc, T_chain_id, [], []) | Pair_key (l, r, _meta) -> ( let tl = unparse_comparable_ty_uncarbonated ~loc l in @@ -238,6 +240,7 @@ let rec unparse_ty_uncarbonated : | Key_t _meta -> prim (T_key, [], []) | Timestamp_t _meta -> prim (T_timestamp, [], []) | Address_t _meta -> prim (T_address, [], []) + | Tx_rollup_l2_address_t _meta -> prim (T_tx_rollup_l2_address, [], []) | Operation_t _meta -> prim (T_operation, [], []) | Chain_id_t _meta -> prim (T_chain_id, [], []) | Never_t _meta -> prim (T_never, [], []) @@ -344,6 +347,7 @@ let[@coq_axiom_with_reason "gadt"] rec comparable_ty_of_ty : | Key_t tname -> ok (Key_key tname, ctxt) | Timestamp_t tname -> ok (Timestamp_key tname, ctxt) | Address_t tname -> ok (Address_key tname, ctxt) + | Tx_rollup_l2_address_t tname -> ok (Tx_rollup_l2_address_key tname, ctxt) | Chain_id_t tname -> ok (Chain_id_key tname, ctxt) | Pair_t (l, r, pname) -> comparable_ty_of_ty ctxt loc l >>? fun (lty, ctxt) -> @@ -417,6 +421,24 @@ let unparse_address ~loc ctxt mode {destination; entrypoint} = in (String (loc, notation), ctxt) +let unparse_tx_rollup_l2_address ~loc ctxt mode + (tx_address : tx_rollup_l2_address) = + Gas.consume ctxt Unparse_costs.contract >|? fun ctxt -> + match tx_address with + | Index i -> (Int (loc, Z.of_int32 i), ctxt) + | Value address -> ( + match mode with + | Optimized | Optimized_legacy -> + let bytes = + Data_encoding.Binary.to_bytes_exn + Tx_rollup_l2_address.encoding + address + in + (Bytes (loc, bytes), ctxt) + | Readable -> + let b58check = Tx_rollup_l2_address.to_b58check address in + (String (loc, b58check), ctxt)) + let unparse_contract ~loc ctxt mode {arg_ty = _; address} = unparse_address ~loc ctxt mode address @@ -588,6 +610,8 @@ let[@coq_axiom_with_reason "gadt"] rec unparse_comparable_data : | (Timestamp_key _, t) -> Lwt.return @@ unparse_timestamp ~loc ctxt mode t | (Address_key _, address) -> Lwt.return @@ unparse_address ~loc ctxt mode address + | (Tx_rollup_l2_address_key _, address) -> + Lwt.return @@ unparse_tx_rollup_l2_address ~loc ctxt mode address | (Signature_key _, s) -> Lwt.return @@ unparse_signature ~loc ctxt mode s | (Mutez_key _, v) -> Lwt.return @@ unparse_mutez ~loc ctxt v | (Key_key _, k) -> Lwt.return @@ unparse_key ~loc ctxt mode k @@ -640,8 +664,8 @@ let hash_comparable_data ctxt typ data = let check_dupable_comparable_ty : type a. a comparable_ty -> unit = function | Unit_key _ | Never_key _ | Int_key _ | Nat_key _ | Signature_key _ | String_key _ | Bytes_key _ | Mutez_key _ | Bool_key _ | Key_hash_key _ - | Key_key _ | Timestamp_key _ | Chain_id_key _ | Address_key _ | Pair_key _ - | Union_key _ | Option_key _ -> + | Key_key _ | Timestamp_key _ | Chain_id_key _ | Address_key _ + | Tx_rollup_l2_address_key _ | Pair_key _ | Union_key _ | Option_key _ -> () let check_dupable_ty ctxt loc ty = @@ -661,6 +685,7 @@ let check_dupable_ty ctxt loc ty = | Key_t _ -> return_unit | Timestamp_t _ -> return_unit | Address_t _ -> return_unit + | Tx_rollup_l2_address_t _ -> return_unit | Bool_t _ -> return_unit | Contract_t (_, _) -> return_unit | Operation_t _ -> return_unit @@ -786,6 +811,8 @@ let rec merge_comparable_types : return (fun annot -> Chain_id_key annot) Eq annot_a annot_b | (Address_key annot_a, Address_key annot_b) -> return (fun annot -> Address_key annot) Eq annot_a annot_b + | (Tx_rollup_l2_address_key annot_a, Tx_rollup_l2_address_key annot_b) -> + return (fun annot -> Tx_rollup_l2_address_key annot) Eq annot_a annot_b | (Pair_key (left_a, right_a, annot_a), Pair_key (left_b, right_b, annot_b)) -> merge_type_metadata annot_a annot_b >>$ fun annot -> @@ -910,6 +937,8 @@ let merge_types : return (fun tname -> Timestamp_t tname) Eq tn1 tn2 | (Address_t tn1, Address_t tn2) -> return (fun tname -> Address_t tname) Eq tn1 tn2 + | (Tx_rollup_l2_address_t tn1, Tx_rollup_l2_address_t tn2) -> + return (fun tname -> Tx_rollup_l2_address_t tname) Eq tn1 tn2 | (Bool_t tn1, Bool_t tn2) -> return (fun tname -> Bool_t tname) Eq tn1 tn2 | (Chain_id_t tn1, Chain_id_t tn2) -> @@ -1170,6 +1199,9 @@ let[@coq_struct "ty"] rec parse_comparable_ty : | Prim (loc, T_address, [], annot) -> check_type_annot loc annot >|? fun () -> (Ex_comparable_ty address_key, ctxt) + | Prim (loc, T_tx_rollup_l2_address, [], annot) -> + check_type_annot loc annot >|? fun () -> + (Ex_comparable_ty tx_rollup_l2_address_key, ctxt) | Prim ( loc, (( T_unit | T_never | T_int | T_nat | T_string | T_bytes | T_mutez @@ -1396,6 +1428,9 @@ and[@coq_axiom_with_reason "complex mutually recursive definition"] parse_ty : check_type_annot loc annot >>? fun () -> ok (Ex_ty timestamp_t, ctxt) | Prim (loc, T_address, [], annot) -> check_type_annot loc annot >>? fun () -> ok (Ex_ty address_t, ctxt) + | Prim (loc, T_tx_rollup_l2_address, [], annot) -> + check_type_annot loc annot >>? fun () -> + ok (Ex_ty tx_rollup_l2_address_t, ctxt) | Prim (loc, T_signature, [], annot) -> check_type_annot loc annot >>? fun () -> ok (Ex_ty signature_t, ctxt) | Prim (loc, T_operation, [], annot) -> @@ -1561,8 +1596,9 @@ and[@coq_axiom_with_reason "complex mutually recursive definition"] parse_ty : | Prim ( loc, (( T_unit | T_signature | T_int | T_nat | T_string | T_bytes | T_mutez - | T_bool | T_key | T_key_hash | T_timestamp | T_address | T_chain_id - | T_operation | T_never ) as prim), + | T_bool | T_key | T_key_hash | T_timestamp | T_address + | T_tx_rollup_l2_address | T_chain_id | T_operation | T_never ) as + prim), l, _ ) -> error (Invalid_arity (loc, prim, 0, List.length l)) @@ -1607,6 +1643,7 @@ and[@coq_axiom_with_reason "complex mutually recursive definition"] parse_ty : T_bls12_381_g2; T_bls12_381_fr; T_ticket; + T_tx_rollup_l2_address; ] and[@coq_axiom_with_reason "complex mutually recursive definition"] parse_big_map_ty @@ -1700,6 +1737,7 @@ let check_packable ~legacy loc root = | Key_t _ -> Result.return_unit | Timestamp_t _ -> Result.return_unit | Address_t _ -> Result.return_unit + | Tx_rollup_l2_address_t _ -> Result.return_unit | Bool_t _ -> Result.return_unit | Chain_id_t _ -> Result.return_unit | Never_t _ -> Result.return_unit @@ -2151,6 +2189,110 @@ let parse_address ctxt : Script.node -> (address * context) tzresult = function | expr -> error @@ Invalid_kind (location expr, [String_kind; Bytes_kind], kind expr) +let parse_tx_rollup_l2_address ctxt : + Script.node -> (tx_rollup_l2_address * context) tzresult = + let open Indexable in + function + | Bytes (loc, bytes) as expr (* As unparsed with [Optimized]. *) -> ( + Gas.consume ctxt Typecheck_costs.tx_rollup_l2_address >>? fun ctxt -> + match Tx_rollup_l2_address.of_bytes_opt bytes with + | Some txa -> ok (Value txa, ctxt) + | None -> + error + @@ Invalid_syntactic_constant + ( loc, + strip_locations expr, + "a valid transaction rollup L2 address" )) + | String (loc, str) as expr (* As unparsed with [Readable]. *) -> ( + Gas.consume ctxt Typecheck_costs.tx_rollup_l2_address >>? fun ctxt -> + match Tx_rollup_l2_address.of_b58check_opt str with + | Some txa -> ok (Value txa, ctxt) + | None -> + error + @@ Invalid_syntactic_constant + ( loc, + strip_locations expr, + "a valid transaction rollup L2 address" )) + | Int (loc, i) as expr -> + Gas.consume ctxt Typecheck_costs.tx_rollup_l2_address >>? fun ctxt -> + if Compare.Z.(Z.zero <= i && i < Z.of_int32 Int32.max_int) then + ok (Index (Int32.of_int @@ Z.to_int i), ctxt) + else + error + @@ Invalid_syntactic_constant + (loc, strip_locations expr, "a valid transaction rollup L2 address") + | expr -> + error @@ Invalid_kind (location expr, [String_kind; Bytes_kind], kind expr) + +let parse_tx_rollup_deposit_parameters : + context -> Script.expr -> (Tx_rollup.deposit_parameters * context) tzresult + = + fun ctxt parameters -> + match root parameters with + | Seq + ( _, + [ + Prim + ( _, + D_Pair, + [ + Prim + ( _, + D_Pair, + [ticketer; Prim (_, D_Pair, [contents; amount], _)], + _ ); + bls; + ], + _ ); + ty; + ] ) -> + parse_tx_rollup_l2_address ctxt bls >>? fun (destination, ctxt) -> + (match amount with + | Int (_, v) when Compare.Z.(Z.zero < v && v <= Z.of_int64 Int64.max_int) + -> + ok @@ Z.to_int64 v + | Int (_, v) -> error @@ Tx_rollup_invalid_ticket_amount v + | expr -> error @@ Invalid_kind (location expr, [Int_kind], kind expr)) + >|? fun amount -> + (Tx_rollup.{ticketer; contents; ty; amount; destination}, ctxt) + | expr -> error @@ Invalid_kind (location expr, [Prim_kind], kind expr) + +let parse_tx_rollup_withdraw_parameters : + context -> Script.expr -> (Tx_rollup.withdraw_parameters * context) tzresult + = + fun ctxt parameters -> + match root parameters with + | Seq + ( _, + [ + Prim + ( _, + D_Pair, + [ + Prim + ( _, + D_Pair, + [ticketer; Prim (_, D_Pair, [contents; amount], _)], + _ ); + destination_contract; + ], + _ ); + ty; + ] ) -> + parse_key_hash ctxt destination_contract + >>? fun (destination_contract, ctxt) -> + let destination_contract = + Contract.implicit_contract destination_contract + in + (match amount with + | Int (_, v) when Compare.Z.(v <= Z.of_int64 Int64.max_int) -> + ok @@ Z.to_int64 v + | Int (_, v) -> error @@ Tx_rollup_invalid_ticket_amount v + | expr -> error @@ Invalid_kind (location expr, [Int_kind], kind expr)) + >|? fun amount -> + (Tx_rollup.{ticketer; contents; ty; amount; destination_contract}, ctxt) + | expr -> error @@ Invalid_kind (location expr, [Prim_kind], kind expr) + let parse_never expr : (never * context) tzresult = error @@ Invalid_never_expr (location expr) @@ -2266,6 +2408,8 @@ let[@coq_axiom_with_reason "gadt"] rec parse_comparable_data : Lwt.return @@ traced_no_lwt @@ parse_chain_id ctxt expr | (Address_key _, expr) -> Lwt.return @@ traced_no_lwt @@ parse_address ctxt expr + | (Tx_rollup_l2_address_key _, expr) -> + Lwt.return @@ traced_no_lwt @@ parse_tx_rollup_l2_address ctxt expr | (Pair_key (tl, tr, _), expr) -> let r_witness = comparable_comb_witness1 tr in let parse_l ctxt v = parse_comparable_data ?type_logger ctxt tl v in @@ -2469,6 +2613,8 @@ let[@coq_axiom_with_reason "gadt"] rec parse_data : Lwt.return @@ traced_no_lwt @@ parse_chain_id ctxt expr | (Address_t _, expr) -> Lwt.return @@ traced_no_lwt @@ parse_address ctxt expr + | (Tx_rollup_l2_address_t _, expr) -> + Lwt.return @@ traced_no_lwt @@ parse_tx_rollup_l2_address ctxt expr | (Contract_t (arg_ty, _), expr) -> traced ( parse_address ctxt expr >>?= fun (address, ctxt) -> @@ -2537,9 +2683,10 @@ let[@coq_axiom_with_reason "gadt"] rec parse_data : if allow_forged then opened_ticket_type (location expr) t >>?= fun ty -> parse_comparable_data ?type_logger ctxt ty expr - >|=? fun (({destination; entrypoint = _}, (contents, amount)), ctxt) -> + >>=? fun (({destination; entrypoint = _}, (contents, amount)), ctxt) -> match destination with - | Contract ticketer -> ({ticketer; contents; amount}, ctxt) + | Contract ticketer -> return ({ticketer; contents; amount}, ctxt) + | Tx_rollup _ -> fail (Unexpected_ticket_owner destination) else traced_fail (Unexpected_forged_value (location expr)) (* Sets *) | (Set_t (t, _ty_name), (Seq (loc, vs) as expr)) -> @@ -4982,8 +5129,8 @@ and[@coq_axiom_with_reason "complex mutually recursive definition"] parse_contra Destination.t -> entrypoint:Entrypoint.t -> (context * arg typed_contract) tzresult Lwt.t = - fun ~stack_depth ~legacy ctxt loc arg contract ~entrypoint -> - match contract with + fun ~stack_depth ~legacy ctxt loc arg destination ~entrypoint -> + match destination with | Contract contract -> ( match Contract.is_implicit contract with | Some _ -> @@ -5029,8 +5176,15 @@ and[@coq_axiom_with_reason "complex mutually recursive definition"] parse_contra loc >>? fun (entrypoint_arg, ctxt) -> entrypoint_arg >|? fun (entrypoint, arg_ty) -> - let destination : Destination.t = Contract contract in (ctxt, {arg_ty; address = {destination; entrypoint}}) ))) + | Tx_rollup tx_rollup -> + Tx_rollup_state.assert_exist ctxt tx_rollup >>=? fun ctxt -> + if Entrypoint.(entrypoint = Tx_rollup.deposit_entrypoint) then + match arg with + | Pair_t (Ticket_t (_, _), Tx_rollup_l2_address_t _, _) -> + return (ctxt, {arg_ty = arg; address = {destination; entrypoint}}) + | _ -> failwith "TODO: bad parameter" + else fail (No_such_entrypoint entrypoint) and parse_view_name ctxt : Script.node -> (Script_string.t * context) tzresult = function @@ -5225,6 +5379,19 @@ let parse_contract_for_script : in (ctxt, Some contract) | Error Inconsistent_types_fast -> (ctxt, None))) ))) + | Tx_rollup tx_rollup -> ( + match arg with + | Pair_t (Ticket_t (_, _), Tx_rollup_l2_address_t _, _) + when Entrypoint.( + entrypoint = Alpha_context.Tx_rollup.deposit_entrypoint) -> ( + Tx_rollup_state.find ctxt tx_rollup >|=? function + | (ctxt, Some _) -> + ( ctxt, + Some + {arg_ty = arg; address = {destination = contract; entrypoint}} + ) + | (ctxt, None) -> (ctxt, None)) + | _ -> return (ctxt, None)) let parse_code : ?type_logger:type_logger -> @@ -5494,6 +5661,8 @@ let[@coq_axiom_with_reason "gadt"] rec unparse_data : | (Timestamp_t _, t) -> Lwt.return @@ unparse_timestamp ~loc ctxt mode t | (Address_t _, address) -> Lwt.return @@ unparse_address ~loc ctxt mode address + | (Tx_rollup_l2_address_t _, address) -> + Lwt.return @@ unparse_tx_rollup_l2_address ~loc ctxt mode address | (Contract_t _, contract) -> Lwt.return @@ unparse_contract ~loc ctxt mode contract | (Signature_t _, s) -> Lwt.return @@ unparse_signature ~loc ctxt mode s @@ -5974,6 +6143,7 @@ let rec has_lazy_storage : type t. t ty -> t has_lazy_storage = | Key_t _ -> False_f | Timestamp_t _ -> False_f | Address_t _ -> False_f + | Tx_rollup_l2_address_t _ -> False_f | Bool_t _ -> False_f | Lambda_t (_, _, _) -> False_f | Set_t (_, _) -> False_f diff --git a/src/proto_alpha/lib_protocol/script_ir_translator.mli b/src/proto_alpha/lib_protocol/script_ir_translator.mli index 41d1db2e7acc6cc744b4c6f01a83f4ebca5f444d..4715fc2db3c5e8c10a288682b801e75d97fe8556 100644 --- a/src/proto_alpha/lib_protocol/script_ir_translator.mli +++ b/src/proto_alpha/lib_protocol/script_ir_translator.mli @@ -404,6 +404,17 @@ val parse_contract_for_script : entrypoint:Entrypoint.t -> (context * 'a Script_typed_ir.typed_contract option) tzresult Lwt.t +(** [parse_tx_rollup_deposit_parameters ctxt expr] extracts from + [expr] the parameters of the [deposit] entrypoint of transaction + rollups. *) +val parse_tx_rollup_deposit_parameters : + context -> Script.expr -> (Tx_rollup.deposit_parameters * context) tzresult + +(** [parse_tx_rollup_withdraw_parameters ctxt script] extracts from [script] + the parameters of the [withdraw] entrypoint of transaction rollups. *) +val parse_tx_rollup_withdraw_parameters : + context -> Script.expr -> (Tx_rollup.withdraw_parameters * context) tzresult + val find_entrypoint : error_details:'error_trace error_details -> 't Script_typed_ir.ty -> diff --git a/src/proto_alpha/lib_protocol/script_tc_errors.ml b/src/proto_alpha/lib_protocol/script_tc_errors.ml index b75572cae9c4b109e8226dfde73ea89211cd7939..231bc42a9df5e927201d4de828b9ff48174be63a 100644 --- a/src/proto_alpha/lib_protocol/script_tc_errors.ml +++ b/src/proto_alpha/lib_protocol/script_tc_errors.ml @@ -68,6 +68,10 @@ type error += Duplicate_entrypoint of Entrypoint.t type error += Unreachable_entrypoint of prim list +(* Transaction rollup errors *) + +type error += Tx_rollup_invalid_ticket_amount of Z.t + (* Instruction typing errors *) type error += Fail_not_in_tail_position of Script.location @@ -196,6 +200,8 @@ type error += Unexpected_forged_value of Script.location type error += Non_dupable_type of Script.location * Script.expr +type error += Unexpected_ticket_owner of Destination.t + (* Merge type errors *) type inconsistent_types_fast_error = diff --git a/src/proto_alpha/lib_protocol/script_tc_errors_registration.ml b/src/proto_alpha/lib_protocol/script_tc_errors_registration.ml index 26e5b3a9e4226368244153a2d48c0b1400352e4f..1c2d2715fd1b6fc5a276147682ff39f984d94c85 100644 --- a/src/proto_alpha/lib_protocol/script_tc_errors_registration.ml +++ b/src/proto_alpha/lib_protocol/script_tc_errors_registration.ml @@ -229,6 +229,17 @@ let () = (obj1 (req "path" (list prim_encoding))) (function Unreachable_entrypoint path -> Some path | _ -> None) (fun path -> Unreachable_entrypoint path) ; + (* Tx rollup invalid ticket amount *) + register_error_kind + `Permanent + ~id:"michelson_v1.invalid_tx_rollup_ticket_amount" + ~title:"Invalid ticket amount" + ~description: + "Ticket amount to be deposited in a transaction rollup should be \ + strictly positive and fit in a signed 64-bit integer" + (obj1 (req "requested_value" Data_encoding.z)) + (function Tx_rollup_invalid_ticket_amount z -> Some z | _ -> None) + (fun z -> Tx_rollup_invalid_ticket_amount z) ; (* Duplicate entrypoint *) register_error_kind `Permanent @@ -787,4 +798,13 @@ let () = ~description:"DUP was used on a non-dupable type (e.g. tickets)." (obj2 (req "loc" location_encoding) (req "type" Script.expr_encoding)) (function Non_dupable_type (loc, ty) -> Some (loc, ty) | _ -> None) - (fun (loc, ty) -> Non_dupable_type (loc, ty)) + (fun (loc, ty) -> Non_dupable_type (loc, ty)) ; + (* Unexpected ticket owner*) + register_error_kind + `Permanent + ~id:"michelson_v1.unexpected_ticket_owner" + ~title:"Unexpected ticket owner" + ~description:"Ticket can only be created by a smart contract" + (obj1 (req "ticketer" Destination.encoding)) + (function Unexpected_ticket_owner t -> Some t | _ -> None) + (fun t -> Unexpected_ticket_owner t) diff --git a/src/proto_alpha/lib_protocol/script_typed_ir.ml b/src/proto_alpha/lib_protocol/script_typed_ir.ml index baddb74f68701a3b76c7986e8f11484e9b00bd99..336e7a8422dd3c175082430c535eddc96aa01374 100644 --- a/src/proto_alpha/lib_protocol/script_typed_ir.ml +++ b/src/proto_alpha/lib_protocol/script_typed_ir.ml @@ -90,6 +90,8 @@ end type signature = Script_signature.t +type tx_rollup_l2_address = Tx_rollup_l2_address.Indexable.t + type ('a, 'b) pair = 'a * 'b type ('a, 'b) union = L of 'a | R of 'b @@ -331,6 +333,9 @@ type _ comparable_ty = Script_chain_id.t ty_metadata -> Script_chain_id.t comparable_ty | Address_key : address ty_metadata -> address comparable_ty + | Tx_rollup_l2_address_key : + tx_rollup_l2_address ty_metadata + -> tx_rollup_l2_address comparable_ty | Pair_key : 'a comparable_ty * 'b comparable_ty * ('a, 'b) pair ty_metadata -> ('a, 'b) pair comparable_ty @@ -356,6 +361,7 @@ let comparable_ty_metadata : type a. a comparable_ty -> a ty_metadata = function | Timestamp_key meta -> meta | Chain_id_key meta -> meta | Address_key meta -> meta + | Tx_rollup_l2_address_key meta -> meta | Pair_key (_, _, meta) -> meta | Union_key (_, _, meta) -> meta | Option_key (_, meta) -> meta @@ -390,6 +396,8 @@ let chain_id_key = Chain_id_key {size = Type_size.one} let address_key = Address_key {size = Type_size.one} +let tx_rollup_l2_address_key = Tx_rollup_l2_address_key {size = Type_size.one} + let pair_key loc l r = Type_size.compound2 loc (comparable_ty_size l) (comparable_ty_size r) >|? fun size -> Pair_key (l, r, {size}) @@ -1287,6 +1295,9 @@ and 'ty ty = | Key_t : public_key ty_metadata -> public_key ty | Timestamp_t : Script_timestamp.t ty_metadata -> Script_timestamp.t ty | Address_t : address ty_metadata -> address ty + | Tx_rollup_l2_address_t : + tx_rollup_l2_address ty_metadata + -> tx_rollup_l2_address ty | Bool_t : bool ty_metadata -> bool ty | Pair_t : 'a ty * 'b ty * ('a, 'b) pair ty_metadata -> ('a, 'b) pair ty | Union_t : @@ -1782,6 +1793,7 @@ let ty_metadata : type a. a ty -> a ty_metadata = function | Timestamp_t meta -> meta | Chain_id_t meta -> meta | Address_t meta -> meta + | Tx_rollup_l2_address_t meta -> meta | Pair_t (_, _, meta) -> meta | Union_t (_, _, meta) -> meta | Option_t (_, meta) -> meta @@ -1827,6 +1839,8 @@ let address_t = Address_t {size = Type_size.one} let bool_t = Bool_t {size = Type_size.one} +let tx_rollup_l2_address_t = Tx_rollup_l2_address_t {size = Type_size.one} + let pair_t loc l r = Type_size.compound2 loc (ty_size l) (ty_size r) >|? fun size -> Pair_t (l, r, {size}) @@ -2129,7 +2143,8 @@ let (ty_traverse, comparable_ty_traverse) = match ty with | Unit_key _ | Int_key _ | Nat_key _ | Signature_key _ | String_key _ | Bytes_key _ | Mutez_key _ | Key_hash_key _ | Key_key _ | Timestamp_key _ - | Address_key _ | Bool_key _ | Chain_id_key _ | Never_key _ -> + | Address_key _ | Tx_rollup_l2_address_key _ | Bool_key _ | Chain_id_key _ + | Never_key _ -> (return [@ocaml.tailcall]) () | Pair_key (ty1, ty2, _) -> (next2 [@ocaml.tailcall]) ty1 ty2 | Union_key (ty1, ty2, _) -> (next2 [@ocaml.tailcall]) ty1 ty2 @@ -2142,7 +2157,7 @@ let (ty_traverse, comparable_ty_traverse) = match (ty : t ty) with | Unit_t _ | Int_t _ | Nat_t _ | Signature_t _ | String_t _ | Bytes_t _ | Mutez_t _ | Key_hash_t _ | Key_t _ | Timestamp_t _ | Address_t _ - | Bool_t _ + | Tx_rollup_l2_address_t _ | Bool_t _ | Sapling_transaction_t (_, _) | Sapling_state_t (_, _) | Operation_t _ | Chain_id_t _ | Never_t _ | Bls12_381_g1_t _ @@ -2224,7 +2239,7 @@ let value_traverse (type t) (ty : (t ty, t comparable_ty) union) (x : t) init f match ty with | Unit_t _ | Int_t _ | Nat_t _ | Signature_t _ | String_t _ | Bytes_t _ | Mutez_t _ | Key_hash_t _ | Key_t _ | Timestamp_t _ | Address_t _ - | Bool_t _ + | Tx_rollup_l2_address_t _ | Bool_t _ | Sapling_transaction_t (_, _) | Sapling_state_t (_, _) | Operation_t _ | Chain_id_t _ | Never_t _ | Bls12_381_g1_t _ @@ -2291,7 +2306,8 @@ let value_traverse (type t) (ty : (t ty, t comparable_ty) union) (x : t) init f match ty with | Unit_key _ | Int_key _ | Nat_key _ | Signature_key _ | String_key _ | Bytes_key _ | Mutez_key _ | Key_hash_key _ | Key_key _ | Timestamp_key _ - | Address_key _ | Bool_key _ | Chain_id_key _ | Never_key _ -> + | Address_key _ | Tx_rollup_l2_address_key _ | Bool_key _ | Chain_id_key _ + | Never_key _ -> (return [@ocaml.tailcall]) () | Pair_key (ty1, ty2, _) -> (next2 [@ocaml.tailcall]) ty1 ty2 (fst x) (snd x) diff --git a/src/proto_alpha/lib_protocol/script_typed_ir.mli b/src/proto_alpha/lib_protocol/script_typed_ir.mli index d67d25402899bd0b769bc0327d64e3bc2f90d79a..4945d8912de476defe90f3fc5c5ee7b16c3b41c6 100644 --- a/src/proto_alpha/lib_protocol/script_typed_ir.mli +++ b/src/proto_alpha/lib_protocol/script_typed_ir.mli @@ -73,6 +73,8 @@ end type signature = Script_signature.t +type tx_rollup_l2_address = Tx_rollup_l2_address.Indexable.t + type ('a, 'b) pair = 'a * 'b type ('a, 'b) union = L of 'a | R of 'b @@ -209,6 +211,9 @@ type _ comparable_ty = Script_chain_id.t ty_metadata -> Script_chain_id.t comparable_ty | Address_key : address ty_metadata -> address comparable_ty + | Tx_rollup_l2_address_key : + tx_rollup_l2_address ty_metadata + -> tx_rollup_l2_address comparable_ty | Pair_key : 'a comparable_ty * 'b comparable_ty * ('a, 'b) pair ty_metadata -> ('a, 'b) pair comparable_ty @@ -247,6 +252,8 @@ val chain_id_key : Script_chain_id.t comparable_ty val address_key : address comparable_ty +val tx_rollup_l2_address_key : tx_rollup_l2_address comparable_ty + val pair_key : Script.location -> 'a comparable_ty -> @@ -1366,6 +1373,9 @@ and 'ty ty = | Key_t : public_key ty_metadata -> public_key ty | Timestamp_t : Script_timestamp.t ty_metadata -> Script_timestamp.t ty | Address_t : address ty_metadata -> address ty + | Tx_rollup_l2_address_t : + tx_rollup_l2_address ty_metadata + -> tx_rollup_l2_address ty | Bool_t : bool ty_metadata -> bool ty | Pair_t : 'a ty * 'b ty * ('a, 'b) pair ty_metadata -> ('a, 'b) pair ty | Union_t : @@ -1550,6 +1560,8 @@ val timestamp_t : Script_timestamp.t ty val address_t : address ty +val tx_rollup_l2_address_t : tx_rollup_l2_address ty + val bool_t : bool ty val pair_t : Script.location -> 'a ty -> 'b ty -> ('a, 'b) pair ty tzresult diff --git a/src/proto_alpha/lib_protocol/script_typed_ir_size.ml b/src/proto_alpha/lib_protocol/script_typed_ir_size.ml index b856ec4ce291010b00c52c0b6f53aadf2a7323bc..03130f401ddaad987e569d704c2de24ceea62d83 100644 --- a/src/proto_alpha/lib_protocol/script_typed_ir_size.ml +++ b/src/proto_alpha/lib_protocol/script_typed_ir_size.ml @@ -55,6 +55,7 @@ let (comparable_ty_size, ty_size) = | Key_key a -> ret_succ_adding accu (base_basic a) | Timestamp_key a -> ret_succ_adding accu (base_basic a) | Address_key a -> ret_succ_adding accu (base_basic a) + | Tx_rollup_l2_address_key a -> ret_succ_adding accu (base_basic a) | Bool_key a -> ret_succ_adding accu (base_basic a) | Chain_id_key a -> ret_succ_adding accu (base_basic a) | Never_key a -> ret_succ_adding accu (base_basic a) @@ -78,6 +79,7 @@ let (comparable_ty_size, ty_size) = | Key_t a -> ret_succ_adding accu @@ base_basic a | Timestamp_t a -> ret_succ_adding accu @@ base_basic a | Address_t a -> ret_succ_adding accu @@ base_basic a + | Tx_rollup_l2_address_t a -> ret_succ_adding accu @@ base_basic a | Bool_t a -> ret_succ_adding accu @@ base_basic a | Operation_t a -> ret_succ_adding accu @@ base_basic a | Chain_id_t a -> ret_succ_adding accu @@ base_basic a @@ -153,6 +155,9 @@ let address_size addr = +! destination_size addr.destination +! Entrypoint.in_memory_size addr.entrypoint +let tx_rollup_l2_address_size (tx : tx_rollup_l2_address) = + Tx_rollup_l2_address.Indexable.in_memory_size tx + let view_signature_size (View_signature {name; input_ty; output_ty}) = ret_adding (ty_size input_ty ++ ty_size output_ty) @@ -264,6 +269,8 @@ let rec value_size : | Key_t _ -> ret_succ_adding accu (public_key_size x) | Timestamp_t _ -> ret_succ_adding accu (timestamp_size x) | Address_t _ -> ret_succ_adding accu (address_size x) + | Tx_rollup_l2_address_t _ -> + ret_succ_adding accu (tx_rollup_l2_address_size x) | Bool_t _ -> ret_succ accu | Pair_t (_, _, _) -> ret_succ_adding accu h2w | Union_t (_, _, _) -> ret_succ_adding accu h1w @@ -325,6 +332,8 @@ let rec value_size : | Key_key _ -> ret_succ_adding accu (public_key_size x) | Timestamp_key _ -> ret_succ_adding accu (timestamp_size x) | Address_key _ -> ret_succ_adding accu (address_size x) + | Tx_rollup_l2_address_key _ -> + ret_succ_adding accu (tx_rollup_l2_address_size x) | Bool_key _ -> ret_succ accu | Pair_key (_, _, _) -> ret_succ_adding accu h2w | Union_key (_, _, _) -> ret_succ_adding accu h1w diff --git a/src/proto_alpha/lib_protocol/stake_storage.ml b/src/proto_alpha/lib_protocol/stake_storage.ml index 34d68b4538f864a436857014c5186fdd2336a0c1..cf5bd6b171497d5e2ffcd2b9b0eb640f7fddf18d 100644 --- a/src/proto_alpha/lib_protocol/stake_storage.ml +++ b/src/proto_alpha/lib_protocol/stake_storage.ml @@ -170,6 +170,16 @@ let snapshot ctxt = Storage.Stake.Staking_balance.snapshot ctxt index >>=? fun ctxt -> Storage.Stake.Active_delegate_with_one_roll.snapshot ctxt index +let full_balance ctxt delegate = + let delegate_contract = Contract_repr.implicit_contract delegate in + Frozen_deposits_storage.get ctxt delegate_contract >>=? fun frozen_deposits -> + Tx_rollup_frozen_storage.frozen_tez ctxt delegate_contract + >>=? fun rollup_frozen_deposits -> + Tez_repr.(frozen_deposits.current_amount +? rollup_frozen_deposits) + >>?= fun frozen -> + Storage.Contract.Balance.get ctxt delegate_contract >>=? fun balance -> + Lwt.return Tez_repr.(frozen +? balance) + let select_distribution_for_cycle ctxt cycle pubkey = Storage.Stake.Last_snapshot.get ctxt >>=? fun max_index -> Storage.Seed.For_cycle.get ctxt cycle >>=? fun seed -> @@ -192,12 +202,7 @@ let select_distribution_for_cycle ctxt cycle pubkey = let delegate_contract = Contract_repr.implicit_contract delegate in Storage.Contract.Frozen_deposits_limit.find ctxt delegate_contract >>=? fun frozen_deposits_limit -> - Storage.Contract.Balance.get ctxt delegate_contract - >>=? fun balance -> - Frozen_deposits_storage.get ctxt delegate_contract - >>=? fun frozen_deposits -> - Tez_repr.(balance +? frozen_deposits.current_amount) - >>?= fun total_balance -> + full_balance ctxt delegate >>=? fun total_balance -> let frozen_deposits_percentage = Constants_storage.frozen_deposits_percentage ctxt in diff --git a/src/proto_alpha/lib_protocol/stake_storage.mli b/src/proto_alpha/lib_protocol/stake_storage.mli index 66984a63211eb7090b5e500a7a7d5e97a587cb84..840a8a7b859d6bf52a07c70ce24cb377c7f37614 100644 --- a/src/proto_alpha/lib_protocol/stake_storage.mli +++ b/src/proto_alpha/lib_protocol/stake_storage.mli @@ -62,6 +62,11 @@ val get_staking_balance : val snapshot : Raw_context.t -> Raw_context.t tzresult Lwt.t +val full_balance : + Raw_context.t -> + Signature.public_key_hash -> + (Tez_repr.t, error trace) result Lwt.t + val select_distribution_for_cycle_do_not_call_except_for_migration : Raw_context.t -> Cycle_repr.t -> diff --git a/src/proto_alpha/lib_protocol/storage.ml b/src/proto_alpha/lib_protocol/storage.ml index 660b3721d7f44526cde80bd244e182583ec48fb4..88a2962b3f8082a86261094bf09df2ed0afb60fe 100644 --- a/src/proto_alpha/lib_protocol/storage.ml +++ b/src/proto_alpha/lib_protocol/storage.ml @@ -1687,6 +1687,239 @@ module Tx_rollup = struct let encoding = Data_encoding.list Tx_rollup_message_repr.hash_encoding end) + + module Level_indexed_context = + Make_indexed_subcontext + (Make_subcontext (Registered) (Raw_context) + (struct + let name = ["tx_rollup_level"] + end)) + (Pair + (Make_index + (Raw_level_repr.Index)) + (Make_index (Tx_rollup_repr.Index))) + + module Bond_indexed_context = + Make_indexed_subcontext + (Make_subcontext (Registered) (Raw_context) + (struct + let name = ["tx_rollup_bond"] + end)) + (Pair + (Make_index + (Tx_rollup_repr.Index)) + (Make_index (Contract_repr.Index))) + + module Contract_indexed_context = + Make_indexed_subcontext + (Make_subcontext (Registered) (Raw_context) + (struct + let name = ["tx_rollup_contract_total_bonds"] + end)) + (Make_index (Contract_repr.Index)) + + module Rollup_indexed_context = + Make_indexed_subcontext + (Make_subcontext (Registered) (Raw_context) + (struct + let name = ["rollup_index"] + end)) + (Make_index (Tx_rollup_repr.Index)) + + module Contract_ticket_indexed_context = + Make_indexed_subcontext + (Make_subcontext (Registered) (Rollup_indexed_context.Raw_context) + (struct + let name = ["tx_rollup_contract_ticket"] + end)) + (Pair + (Make_index + (Contract_repr.Index)) + (Make_index (Ticket_hash_repr.Index))) + + module Frozen_commitments = + Contract_indexed_context.Make_map + (struct + let name = ["tx_rollup_contract_total"] + end) + (struct + type t = Tez_repr.t + + let encoding = Tez_repr.encoding + end) + + module Commitment_list = + Level_indexed_context.Make_carbonated_map + (struct + let name = ["commitment_list"] + end) + (struct + type t = Tx_rollup_commitments_repr.t + + let encoding = Tx_rollup_commitments_repr.encoding + end) + + module Commitment_bond = + Bond_indexed_context.Make_carbonated_map + (struct + let name = ["commitment_bond"] + end) + (struct + type t = int * Tez_repr.t + + let encoding = + Data_encoding.( + obj2 + (req "outstanding_commitments" int31) + (req "bond" Tez_repr.encoding)) + end) + + module Level_tx_rollup_commitment_context = + Make_indexed_subcontext + (Make_subcontext (Registered) (Level_context.Raw_context) + (struct + let name = ["tx_rollup_commitment_index"] + end)) + (Make_index (Tx_rollup_repr.Index)) + + module Prerejection_context = + Make_indexed_subcontext + (Make_subcontext (Registered) (Raw_context) + (struct + let name = ["tx_rollup_prerejection_index"] + end)) + (Make_index (Tx_rollup_rejection_repr.Rejection_hash.Index)) + + module Prerejection = + Prerejection_context.Make_carbonated_map + (struct + let name = ["prerejection"] + end) + (Encoding.Z) + + module Z_context = + Make_indexed_subcontext + (Make_subcontext (Registered) (Raw_context) + (struct + let name = ["tx_rollup_prerejection_by_index"] + end)) + (Make_index (struct + type t = Z.t + + let compare = Z.compare + + let encoding = Data_encoding.z + + let rpc_arg = + let construct = Z.to_string in + let destruct hash = ok @@ Z.of_string hash in + RPC_arg.make + ~descr:"The index of a prerejection" + ~name:"prerejection_index" + ~construct + ~destruct + () + + let path_length = 1 + + let to_path z l = Z.to_string z :: l + + let of_path = function + | [] | _ :: _ :: _ -> None + | [z] -> Some (Z.of_string z) + end)) + + module Prerejection_by_index = + Z_context.Make_carbonated_map + (struct + let name = ["tx_rollup_prerejection_by_index"] + end) + (struct + type t = Tx_rollup_rejection_repr.Rejection_hash.t * Raw_level_repr.t + + let encoding = + Data_encoding.( + obj2 + (req "hash" Tx_rollup_rejection_repr.Rejection_hash.encoding) + (req "level" Raw_level_repr.encoding)) + end) + + module Prerejection_counter = + Make_single_data_storage (Registered) (Raw_context) + (struct + let name = ["prerejection_counter"] + end) + (Encoding.Z) + + module Oldest_prerejection = + Make_single_data_storage (Registered) (Raw_context) + (struct + let name = ["oldest_prerejection"] + end) + (Encoding.Z) + + module Successful_prerejections : + Non_iterable_indexed_carbonated_data_storage_with_values + with type key = Tx_rollup_commitments_repr.Commitment_hash.t + and type value = Z.t * Contract_repr.t + and type t := (Raw_context.t * Raw_level_repr.t) * Tx_rollup_repr.t = + struct + module I = + Storage_functors.Make_indexed_carbonated_data_storage + (Make_subcontext + (Registered) + (Level_tx_rollup_commitment_context.Raw_context) + (struct + let name = ["succesful_prerejections"] + end)) + (Make_index (Tx_rollup_commitments_repr.Commitment.Index)) + (struct + type t = Z.t * Contract_repr.t + + let encoding = + Data_encoding.( + obj2 + (req "index" Data_encoding.z) + (req "contract" Contract_repr.encoding)) + end) + + type context = I.context + + type key = I.key + + type value = I.value + + let mem = I.mem + + let remove_existing = I.remove_existing + + let remove = I.remove + + let update = I.update + + let add_or_remove = I.add_or_remove + + let init = I.init + + let add = I.add + + let list_values = I.list_values + + let get = I.get + + let find = I.find + end + + module Ticket_offramp = + Contract_ticket_indexed_context.Make_carbonated_map + (struct + let name = ["ticket_offramp"] + end) + (struct + type t = Z.t + + let encoding = Data_encoding.z + end) end module Sc_rollup = struct diff --git a/src/proto_alpha/lib_protocol/storage.mli b/src/proto_alpha/lib_protocol/storage.mli index 9e27b8bbe615635e5790be9da38a06bce1d242b3..72704f6d9849af1f6534fa1de9912fc0fc55d33e 100644 --- a/src/proto_alpha/lib_protocol/storage.mli +++ b/src/proto_alpha/lib_protocol/storage.mli @@ -732,6 +732,106 @@ module Tx_rollup : sig init:'a -> f:(Tx_rollup_repr.t -> 'a -> 'a Lwt.t) -> 'a Lwt.t + + (* This tracks the tez frozen for rollup bonds. The tez is still + available for staking and voting, but it has been transferred + so that it cannot be spent. *) + module Frozen_commitments : + Indexed_data_storage + with type key = Contract_repr.t + and type value = Tez_repr.t + and type t := Raw_context.t + + (* A list of the commitments for each rollup and level. The level, + here, is the level committed to (not the level the commitment was + submitted). Usually this list will be of size zero or one, since + there is only one valid commitment for each level. The list is + ordered by reverse priority -- that is, the first-submitted one is + last. *) + module Commitment_list : + Non_iterable_indexed_carbonated_data_storage + with type key = Raw_level_repr.t * Tx_rollup_repr.t + and type value = Tx_rollup_commitments_repr.t + and type t := Raw_context.t + + (* This stores information about which contracts have bonds + for each rollup, and how many commitments those bonds + stake. *) + module Commitment_bond : + Non_iterable_indexed_carbonated_data_storage + with type key = Tx_rollup_repr.t * Contract_repr.t + (* The value here is the number of outstanding commitments and + the amount of the commitment *) + and type value = int * Tez_repr.t + and type t := Raw_context.t + + (** Track prerejections. Before a rejection can be submitted, a + pre-rejection must be submitted by the same contract which will submit + the rejection. A pre-rejection contains a hash of the commitment with a + nonce. Regardless of the order in which rejections are submitted, the + first pre-rejection submitted has priority. This dramatically reduces + the incentives for front-running. Here, we just store the + pre-rejections themselves and their priorit, so that we can quickly + check their existence when a rejection is filed.*) + module Prerejection : + Non_iterable_indexed_carbonated_data_storage + with type key = Tx_rollup_rejection_repr.Rejection_hash.t + and type value = Z.t + and type t := Raw_context.t + + (* Since there is no Carbonated_single_data_storage, this is + uncarbonated. It would be nice to carbonate this, but since we + know that it is only touched during prerejection, we can just + build the cost into the cost of a prerejection operation. *) + module Prerejection_counter : + Single_data_storage with type value = Z.t and type t := Raw_context.t + + (* Same non-carbonation story as Prerejection_counter *) + module Oldest_prerejection : + Single_data_storage with type value = Z.t and type t := Raw_context.t + + (* This is an ordered list of prerejection by counter, which corresponds + to submission order. We use this for garbage collection. When we add + a new prerejection, we can garbage-collect any rejections that are old + enough by doing a sequential search. We can put a limit on the number + that we gc in any one prerejection to keep computation bounded -- as + long as that limit is 2 or more, the storage will also eventually get + reclaimed. Since each prerejection operation will (a) examine at most + one prerejection that it doesn't delete, and (b) introduce at most one + prerejection which will need deleting once, this is amortized O(1). + *) + module Prerejection_by_index : + Non_iterable_indexed_carbonated_data_storage + with type key = Z.t + and type value := + Tx_rollup_rejection_repr.Rejection_hash.t * Raw_level_repr.t + and type t := Raw_context.t + + module Successful_prerejections : sig + include + Non_iterable_indexed_carbonated_data_storage + with type key = Tx_rollup_commitments_repr.Commitment_hash.t + and type value = Z.t * Contract_repr.t + and type t := (Raw_context.t * Raw_level_repr.t) * Tx_rollup_repr.t + + (** HACK *) + val list_values : + ?offset:int -> + ?length:int -> + (Raw_context.t * Raw_level_repr.t) * Tx_rollup_repr.t -> + (Raw_context.t * (Z.t * Contract_repr.t) list) tzresult Lwt.t + end + + (** In order to withdraw a ticket from a rollup, a l2 operation removes the + ticket from the l2 ledger. This will be reflected in the effects of the + block's commitment. When a commitment is finalized, its effects will be + reflected in this table. + *) + module Ticket_offramp : + Non_iterable_indexed_carbonated_data_storage + with type key = Contract_repr.t * Ticket_hash_repr.t + and type value = Z.t + and type t = Raw_context.t * Tx_rollup_repr.t end module Sc_rollup : sig diff --git a/src/proto_alpha/lib_protocol/test/helpers/block.ml b/src/proto_alpha/lib_protocol/test/helpers/block.ml index 3edf62adb745d33bf09c245736941ad8a10e8051..a17b46c29934a8373350ee5c117deab25ef2a49b 100644 --- a/src/proto_alpha/lib_protocol/test/helpers/block.ml +++ b/src/proto_alpha/lib_protocol/test/helpers/block.ml @@ -692,11 +692,15 @@ let bake_n_with_all_balance_updates ?(baking_mode = Application) ?policy match r with | Reveal_result _ | Delegation_result _ | Set_deposits_limit_result _ | Tx_rollup_origination_result _ - | Tx_rollup_submit_batch_result _ | Sc_rollup_originate_result _ + | Tx_rollup_submit_batch_result _ | Tx_rollup_commit_result _ + | Tx_rollup_return_bond_result _ | Sc_rollup_originate_result _ + | Tx_rollup_rejection_result _ | Tx_rollup_prerejection_result _ | Sc_rollup_add_messages_result _ -> balance_updates_rev | Transaction_result (Transaction_to_contract_result {balance_updates; _}) + | Transaction_result + (Transaction_to_tx_rollup_result {balance_updates; _}) | Origination_result {balance_updates; _} | Register_global_constant_result {balance_updates; _} -> List.rev_append balance_updates balance_updates_rev) @@ -724,6 +728,10 @@ let bake_n_with_origination_results ?(baking_mode = Application) ?policy n b = | Successful_manager_result (Set_deposits_limit_result _) | Successful_manager_result (Tx_rollup_origination_result _) | Successful_manager_result (Tx_rollup_submit_batch_result _) + | Successful_manager_result (Tx_rollup_commit_result _) + | Successful_manager_result (Tx_rollup_return_bond_result _) + | Successful_manager_result (Tx_rollup_rejection_result _) + | Successful_manager_result (Tx_rollup_prerejection_result _) | Successful_manager_result (Sc_rollup_originate_result _) | Successful_manager_result (Sc_rollup_add_messages_result _) -> origination_results_rev diff --git a/src/proto_alpha/lib_protocol/test/helpers/op.ml b/src/proto_alpha/lib_protocol/test/helpers/op.ml index 3b53df76d0547183cfb9cd33dc0edcb5f9a6bc69..5d77a7317833f8929b062df6fba7b7d89b3b9ead 100644 --- a/src/proto_alpha/lib_protocol/test/helpers/op.ml +++ b/src/proto_alpha/lib_protocol/test/helpers/op.ml @@ -354,15 +354,28 @@ let miss_signed_endorsement ?level ~endorsed_block ctxt = let delegate = Account.find_alternate real_delegate_pkh in endorsement ~delegate:(delegate.pkh, slots) ~level ~endorsed_block ctxt () -let transaction ?counter ?fee ?gas_limit ?storage_limit +let unsafe_transaction ?counter ?fee ?gas_limit ?storage_limit ?(parameters = Script.unit_parameter) ?(entrypoint = Entrypoint.default) - ctxt (src : Contract.t) (dst : Contract.t) (amount : Tez.t) = - let destination = Destination.Contract dst in + ctxt (src : Contract.t) (destination : Destination.t) (amount : Tez.t) = let top = Transaction {amount; parameters; destination; entrypoint} in manager_operation ?counter ?fee ?gas_limit ?storage_limit ~source:src ctxt top >>=? fun sop -> Context.Contract.manager ctxt src >|=? fun account -> sign account.sk ctxt sop +let transaction ?counter ?fee ?gas_limit ?storage_limit ?parameters ?entrypoint + ctxt (src : Contract.t) (dst : Contract.t) (amount : Tez.t) = + unsafe_transaction + ?counter + ?fee + ?gas_limit + ?storage_limit + ?parameters + ?entrypoint + ctxt + src + (Contract dst) + amount + let delegation ?fee ctxt source dst = let top = Delegation dst in manager_operation @@ -538,3 +551,73 @@ let sc_rollup_origination ?counter ?fee ?gas_limit ?storage_limit ctxt >>=? fun to_sign_op -> Context.Contract.manager ctxt src >|=? fun account -> sign account.sk ctxt to_sign_op + +let tx_rollup_commit ?counter ?fee ?gas_limit ?storage_limit ctxt + (source : Contract.t) (rollup : Tx_rollup.t) + (commitment : Tx_rollup_commitments.Commitment.t) = + manager_operation + ?counter + ?fee + ?gas_limit + ?storage_limit + ~source + ctxt + (Tx_rollup_commit {rollup; commitment}) + >>=? fun to_sign_op -> + Context.Contract.manager ctxt source >|=? fun account -> + sign account.sk ctxt to_sign_op + +let tx_rollup_return_bond ?counter ?fee ?gas_limit ?storage_limit ctxt + (source : Contract.t) (rollup : Tx_rollup.t) = + manager_operation + ?counter + ?fee + ?gas_limit + ?storage_limit + ~source + ctxt + (Tx_rollup_return_bond {rollup}) + >>=? fun to_sign_op -> + Context.Contract.manager ctxt source >|=? fun account -> + sign account.sk ctxt to_sign_op + +let tx_rollup_reject ?counter ?fee ?gas_limit ?storage_limit ctxt + (source : Contract.t) (rollup : Tx_rollup.t) (level : Raw_level.t) + (hash : Tx_rollup_commitments.Commitment_hash.t) (batch_index : int) + (batch : Tx_rollup_message.t) (nonce : int64) = + manager_operation + ?counter + ?fee + ?gas_limit + ?storage_limit + ~source + ctxt + (Tx_rollup_rejection {rollup; level; hash; batch_index; batch; nonce}) + >>=? fun to_sign_op -> + Context.Contract.manager ctxt source >|=? fun account -> + sign account.sk ctxt to_sign_op + +let tx_rollup_prereject ?counter ?fee ?gas_limit ?storage_limit ctxt + (source : Contract.t) (rollup : Tx_rollup.t) (level : Raw_level.t) + (hash : Tx_rollup_commitments.Commitment_hash.t) (batch_index : int) + (nonce : int64) = + let hash = + Tx_rollup_rejection.generate_prerejection + ~nonce + ~source + ~rollup + ~level + ~commitment_hash:hash + ~batch_index + in + manager_operation + ?counter + ?fee + ?gas_limit + ?storage_limit + ~source + ctxt + (Tx_rollup_prerejection {hash}) + >>=? fun to_sign_op -> + Context.Contract.manager ctxt source >|=? fun account -> + sign account.sk ctxt to_sign_op diff --git a/src/proto_alpha/lib_protocol/test/helpers/op.mli b/src/proto_alpha/lib_protocol/test/helpers/op.mli index ea51e7812696763df295ea7ed5554dbac50b1d87..073f447c98d21253e918e14833f1a8b065fcd2f2 100644 --- a/src/proto_alpha/lib_protocol/test/helpers/op.mli +++ b/src/proto_alpha/lib_protocol/test/helpers/op.mli @@ -69,6 +69,26 @@ val transaction : Tez.t -> Operation.packed tzresult Lwt.t +(** Same as [transaction], but with a more generic destination + parameter. It is said unsafe because it can construct transactions + that will always fail, such as + + {ul {li Transaction to the deposit entrypoint of a transaction rollup, + as these transactions are necessarily internals.}} + *) +val unsafe_transaction : + ?counter:Z.t -> + ?fee:Tez.tez -> + ?gas_limit:Gas.Arith.integral -> + ?storage_limit:Z.t -> + ?parameters:Script.lazy_expr -> + ?entrypoint:Entrypoint.t -> + Context.t -> + Contract.t -> + Destination.t -> + Tez.t -> + Operation.packed tzresult Lwt.t + val delegation : ?fee:Tez.tez -> Context.t -> @@ -230,3 +250,60 @@ val sc_rollup_origination : Sc_rollup.Kind.t -> Sc_rollup.PVM.boot_sector -> packed_operation tzresult Lwt.t + +(** [tx_rollup_commit ctxt source tx_rollup commitment] Commits to a tx + rollup state. *) +val tx_rollup_commit : + ?counter:Z.t -> + ?fee:Tez.tez -> + ?gas_limit:Gas.Arith.integral -> + ?storage_limit:Z.t -> + Context.t -> + Contract.t -> + Tx_rollup.t -> + Tx_rollup_commitments.Commitment.t -> + Operation.packed tzresult Lwt.t + +(** [tx_rollup_return_bond ctxt source tx_rollup] returns a commitment bond. *) +val tx_rollup_return_bond : + ?counter:Z.t -> + ?fee:Tez.tez -> + ?gas_limit:Gas.Arith.integral -> + ?storage_limit:Z.t -> + Context.t -> + Contract.t -> + Tx_rollup.t -> + Operation.packed tzresult Lwt.t + +(** [tx_rollup_reject ctxt source tx_rollup level hash batch_index batch nonce] + rejects a commitment. *) +val tx_rollup_reject : + ?counter:counter -> + ?fee:Tez.t -> + ?gas_limit:Gas.Arith.integral -> + ?storage_limit:counter -> + Context.t -> + Contract.t -> + Tx_rollup.t -> + Raw_level.t -> + Tx_rollup_commitments.Commitment_hash.t -> + int -> + Tx_rollup_message.t -> + int64 -> + Operation.packed tzresult Lwt.t + +(** [tx_rollup_prereject ctxt source tx_rollup level hash nonce batch_index] + creates a prerejection to prepare for a rejection. *) +val tx_rollup_prereject : + ?counter:counter -> + ?fee:Tez.t -> + ?gas_limit:Gas.Arith.integral -> + ?storage_limit:counter -> + Context.t -> + Contract.t -> + Tx_rollup.t -> + Raw_level.t -> + Tx_rollup_commitments.Commitment_hash.t -> + int -> + int64 -> + Operation.packed tzresult Lwt.t diff --git a/src/proto_alpha/lib_protocol/test/integration/operations/contracts/tx_rollup_deposit.tz b/src/proto_alpha/lib_protocol/test/integration/operations/contracts/tx_rollup_deposit.tz new file mode 100644 index 0000000000000000000000000000000000000000..7f10911746bdfcdaf2d5077b11e0ffcd982ec6b0 --- /dev/null +++ b/src/proto_alpha/lib_protocol/test/integration/operations/contracts/tx_rollup_deposit.tz @@ -0,0 +1,33 @@ +parameter (pair address tx_rollup_l2_address); +storage (unit); +code { + # cast the address to contract type + CAR; + UNPAIR; + CONTRACT %deposit (pair (ticket unit) tx_rollup_l2_address); + + IF_SOME { + SWAP; + + # amount for transfering + PUSH mutez 0; + SWAP; + + # create a ticket + PUSH nat 10; + PUSH unit Unit; + TICKET; + + PAIR ; + + # deposit + TRANSFER_TOKENS; + + DIP { NIL operation }; + CONS; + + DIP { PUSH unit Unit }; + PAIR; + } + { FAIL ; } + } diff --git a/src/proto_alpha/lib_protocol/test/integration/operations/contracts/tx_rollup_deposit_incorrect_entrypoint.tz b/src/proto_alpha/lib_protocol/test/integration/operations/contracts/tx_rollup_deposit_incorrect_entrypoint.tz new file mode 100644 index 0000000000000000000000000000000000000000..3ad04d1bc0183a01d0a4f85dfa9ed363e972a4d7 --- /dev/null +++ b/src/proto_alpha/lib_protocol/test/integration/operations/contracts/tx_rollup_deposit_incorrect_entrypoint.tz @@ -0,0 +1,33 @@ +parameter (pair address tx_rollup_l2_address); +storage (unit); +code { + # cast the address to contract type + CAR; + UNPAIR; + CONTRACT %default (pair (ticket unit) tx_rollup_l2_address); + + IF_SOME { + SWAP; + + # amount for transfering + PUSH mutez 0; + SWAP; + + # create a ticket + PUSH nat 10; + PUSH unit Unit; + TICKET; + + PAIR ; + + # deposit + TRANSFER_TOKENS; + + DIP { NIL operation }; + CONS; + + DIP { PUSH unit Unit }; + PAIR; + } + { FAIL ; } + } diff --git a/src/proto_alpha/lib_protocol/test/integration/operations/contracts/tx_rollup_deposit_incorrect_param.tz b/src/proto_alpha/lib_protocol/test/integration/operations/contracts/tx_rollup_deposit_incorrect_param.tz new file mode 100644 index 0000000000000000000000000000000000000000..96590ef8a61e4673a6804c0a6498798cb8fe511b --- /dev/null +++ b/src/proto_alpha/lib_protocol/test/integration/operations/contracts/tx_rollup_deposit_incorrect_param.tz @@ -0,0 +1,25 @@ +parameter (address); +storage (unit); +code { + # cast the address to contract type + CAR; + CONTRACT %deposit (nat); + + IF_SOME { + # amount for transfering + PUSH mutez 0; + + # create a ticket + PUSH nat 100; + + # deposit + TRANSFER_TOKENS; + + DIP { NIL operation }; + CONS; + + DIP { PUSH unit Unit }; + PAIR; + } + { FAIL ; } + } \ No newline at end of file diff --git a/src/proto_alpha/lib_protocol/test/integration/operations/contracts/tx_rollup_deposit_one_mutez.tz b/src/proto_alpha/lib_protocol/test/integration/operations/contracts/tx_rollup_deposit_one_mutez.tz new file mode 100644 index 0000000000000000000000000000000000000000..58eb3095cdeab1616887a78946b8a769c50c4b19 --- /dev/null +++ b/src/proto_alpha/lib_protocol/test/integration/operations/contracts/tx_rollup_deposit_one_mutez.tz @@ -0,0 +1,33 @@ +parameter (pair address tx_rollup_l2_address); +storage (unit); +code { + # cast the address to contract type + CAR; + UNPAIR; + CONTRACT %deposit (pair (ticket unit) tx_rollup_l2_address); + + IF_SOME { + SWAP; + + # amount for transfering + PUSH mutez 1; + SWAP; + + # create a ticket + PUSH nat 10; + PUSH unit Unit; + TICKET; + + PAIR ; + + # deposit + TRANSFER_TOKENS; + + DIP { NIL operation }; + CONS; + + DIP { PUSH unit Unit }; + PAIR; + } + { FAIL ; } + } diff --git a/src/proto_alpha/lib_protocol/test/integration/operations/dune b/src/proto_alpha/lib_protocol/test/integration/operations/dune index 60fcd15cc751507cc134ad43c57942043a21a255..13babc23c207937d8d0709cfe4baefd3f93b0b93 100644 --- a/src/proto_alpha/lib_protocol/test/integration/operations/dune +++ b/src/proto_alpha/lib_protocol/test/integration/operations/dune @@ -1,6 +1,7 @@ (test (name main) (package tezos-protocol-alpha-tests) + (deps (glob_files contracts/*)) (libraries alcotest-lwt tezos-base tezos-protocol-alpha @@ -8,5 +9,6 @@ tezos-alpha-test-helpers) (flags (:standard -open Tezos_base__TzPervasives -open Tezos_protocol_alpha + -open Tezos_client_alpha -open Tezos_alpha_test_helpers -open Tezos_base_test_helpers))) diff --git a/src/proto_alpha/lib_protocol/test/integration/operations/test_tx_rollup.ml b/src/proto_alpha/lib_protocol/test/integration/operations/test_tx_rollup.ml index ce5e9d823ed79828b6cd69e49f5435f957de17b4..b5ac97820d159e62482f1a9a30906bcdf0ef36f5 100644 --- a/src/proto_alpha/lib_protocol/test/integration/operations/test_tx_rollup.ml +++ b/src/proto_alpha/lib_protocol/test/integration/operations/test_tx_rollup.ml @@ -3,6 +3,7 @@ (* Open Source License *) (* Copyright (c) 2021 Marigold *) (* Copyright (c) 2021 Nomadic Labs *) +(* Copyright (c) 2022 Oxhead Alpha *) (* *) (* Permission is hereby granted, free of charge, to any person obtaining a *) (* copy of this software and associated documentation files (the "Software"),*) @@ -27,9 +28,8 @@ (** Testing ------- Component: Rollup layer 1 logic - Invocation: dune exec \ - src/proto_alpha/lib_protocol/test/integration/operations/main.exe \ - -- test "^tx rollup$" + Invocation: cd src/proto_alpha/lib_protocol/test/integration/operations \ + && dune exec ./main.exe -- test "^tx rollup$" Subject: Test rollup *) @@ -74,6 +74,8 @@ let message_hash_testable : Tx_rollup_message.hash Alcotest.testable = let wrap m = m >|= Environment.wrap_tzresult +let z_testable = Alcotest.testable Z.pp_print Z.equal + (** [inbox_fees state size] computes the fees (per byte of message) one has to pay to submit a message to the current inbox. *) let inbox_fees state size = @@ -138,11 +140,146 @@ let init_originate_and_submit ?(batch = String.make 5 'c') () = Block.bake ~operation b >>=? fun b -> return ((contract, balance), state, tx_rollup, b) +(** [make_unit_ticket_key ctxt ticketer tx_rollup] computes the key hash of + the unit ticket crafted by [ticketer] and owned by [tx_rollup]. *) +let make_unit_ticket_key ctxt ticketer tx_rollup = + let open Tezos_micheline.Micheline in + let open Michelson_v1_primitives in + let ticketer = + Bytes (0, Data_encoding.Binary.to_bytes_exn Contract.encoding ticketer) + in + let ty = Prim (0, T_unit, [], []) in + let contents = Prim (0, D_Unit, [], []) in + match + Alpha_context.Tx_rollup.hash_ticket ctxt ~ticketer ~ty ~contents tx_rollup + with + | Ok (x, _) -> x + | Error _ -> raise (Invalid_argument "make_unit_ticket_key") + +let commitment_hash_testable = + Alcotest.testable + Tx_rollup_commitments.Commitment_hash.pp + Tx_rollup_commitments.Commitment_hash.( = ) + +let contract_testable = Alcotest.testable Contract.pp Contract.( = ) + +let raw_level_testable = Alcotest.testable Raw_level.pp Raw_level.( = ) + +let rng_state = Random.State.make_self_init () + +let gen_l2_account () = + let seed = + Bytes.init 32 (fun _ -> char_of_int @@ Random.State.int rng_state 255) + in + let secret_key = Bls12_381.Signature.generate_sk seed in + let public_key = Bls12_381.Signature.derive_pk secret_key in + (secret_key, public_key, Tx_rollup_l2_address.of_bls_pk public_key) + +let is_implicit_exn x = + match Alpha_context.Contract.is_implicit x with + | Some x -> x + | None -> raise (Invalid_argument "is_implicit_exn") + +(** [expression_from_string] parses a Michelson expression from a string. *) +let expression_from_string str = + let (ast, errs) = Michelson_v1_parser.parse_expression ~check:true str in + match errs with + | [] -> ast.expanded + | _ -> Stdlib.failwith ("parse expression: " ^ str) + +let print_deposit_arg tx_rollup account = + let open Alpha_context.Script in + Format.sprintf + "Pair \"%s\" %s" + (match tx_rollup with + | `Typed pk -> Tx_rollup.to_b58check pk + | `Raw str -> str) + (match account with + | `Hash pk -> Format.sprintf "\"%s\"" (Tx_rollup_l2_address.to_b58check pk) + | `Raw str -> str) + |> fun x -> + Format.printf "%s\n@?" x ; + x |> expression_from_string |> lazy_expr + +let check_bond ctxt tx_rollup contract count rollup_count = + wrap + (Tx_rollup_commitments.pending_bonded_commitments ctxt tx_rollup contract) + >>=? fun (ctxt, pending) -> + Alcotest.(check int "Pending commitment count correct" count pending) ; + wrap (Tx_rollup.frozen_tez ctxt contract) >>=? fun frozen -> + let bond = Constants.tx_rollup_commitment_bond ctxt in + wrap (Lwt.return @@ Tez.(bond *? Int64.of_int rollup_count)) + >>=? fun expected -> Assert.equal_tez ~loc:__LOC__ expected frozen + +let rec bake_until i top = + let level = Incremental.level i in + if level >= top then return i + else + Incremental.finalize_block i >>=? fun b -> + Incremental.begin_construction b >>=? fun i -> bake_until i top + +let encoding_roundtrip encoding eq value = + let encoded = Data_encoding.Binary.to_bytes_exn encoding value in + match Data_encoding.Binary.of_bytes encoding encoded with + | Ok decoded -> assert (eq decoded value) + | Error _ -> Stdlib.failwith "Decoding failed" + let assert_ok res = match res with Ok r -> r | Error _ -> assert false let raw_level level = assert_ok @@ Raw_level.of_int32 level (** ---- TESTS -------------------------------------------------------------- *) +let test_encoding () = + Context.init ~tx_rollup_enable:true 1 >>=? fun (b, contracts) -> + let contract = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 0 + in + Incremental.begin_construction b >>=? fun i -> + Op.tx_rollup_origination (I i) contract >>=? fun (op, tx_rollup) -> + Incremental.add_operation i op >>=? fun i -> + let state = + Tx_rollup_state.Internal_for_tests.initial_state_with_fees_per_byte + Tez.one_mutez + in + encoding_roundtrip Tx_rollup_state.encoding Tx_rollup_state.( = ) state ; + let commitment : Tx_rollup_commitments.Commitment.t = + {level = raw_level 2l; batches = []; predecessor = None} + in + encoding_roundtrip + Tx_rollup_commitments.Commitment.encoding + Tx_rollup_commitments.Commitment.( = ) + commitment ; + let hash = Tx_rollup_commitments.Commitment.hash commitment in + encoding_roundtrip + Tx_rollup_commitments.Commitment_hash.encoding + Tx_rollup_commitments.Commitment_hash.( = ) + hash ; + + wrap (Lwt.return @@ Tx_rollup_message.make_batch (Incremental.alpha_ctxt i) "") + >>=? fun (batch, _) -> + let rejection : Tx_rollup_rejection.t = + {rollup = tx_rollup; level = raw_level 2l; hash; batch_index = 11; batch} + in + encoding_roundtrip + Tx_rollup_rejection.encoding + Tx_rollup_rejection.( = ) + rejection ; + + let rejection_hash = + Tx_rollup_rejection.generate_prerejection + ~nonce:100L + ~source:contract + ~rollup:tx_rollup + ~level:(raw_level 2l) + ~commitment_hash:hash + ~batch_index:0 + in + encoding_roundtrip + Tx_rollup_rejection.Rejection_hash.encoding + Tx_rollup_rejection.Rejection_hash.( = ) + rejection_hash ; + ignore i ; + return () (** [test_origination] originates a transaction rollup and checks that it burns the expected quantity of xtz. *) @@ -383,7 +520,219 @@ let test_inbox_too_big () = | _ -> false)) >>=? fun _i -> return_unit) -(** Test that block finalization changes gas rates. *) +(** [test_valid_deposit] checks that a smart contract can deposit + tickets to a transaction rollup. *) +let test_valid_deposit () = + let (_, _, pkh) = gen_l2_account () in + + context_init 1 >>=? fun (b, contracts) -> + let account = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 0 + in + originate b account >>=? fun (b, tx_rollup) -> + Contract_helpers.originate_contract + "contracts/tx_rollup_deposit.tz" + "Unit" + account + b + (is_implicit_exn account) + >>=? fun (contract, b) -> + let parameters = print_deposit_arg (`Typed tx_rollup) (`Hash pkh) in + let fee = Test_tez.of_int 10 in + Op.transaction + ~counter:(Z.of_int 2) + ~fee + (B b) + account + contract + Tez.zero + ~parameters + >>=? fun operation -> + Block.bake ~operation b >>=? fun b -> + Incremental.begin_construction b >|=? Incremental.alpha_ctxt >>=? fun ctxt -> + Context.Tx_rollup.inbox (B b) tx_rollup >>=? function + | {contents = [hash]; _} -> + let ticket_hash = make_unit_ticket_key ctxt contract tx_rollup in + let (message, _size) = + Tx_rollup_message.make_deposit (Value pkh) ticket_hash 10L + in + let expected = Tx_rollup_message.hash message in + Alcotest.(check message_hash_testable "deposit" hash expected) ; + return_unit + | _ -> Alcotest.fail "The inbox has not the expected shape" + +(** [test_valid_deposit_inexistant_rollup] checks that the Michelson + interpreter checks the existence of a transaction rollup prior to + sending a deposit order. *) +let test_valid_deposit_inexistant_rollup () = + context_init 1 >>=? fun (b, contracts) -> + let account = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 0 + in + Contract_helpers.originate_contract + "contracts/tx_rollup_deposit.tz" + "Unit" + account + b + (is_implicit_exn account) + >>=? fun (contract, b) -> + Incremental.begin_construction b >>=? fun i -> + let parameters = + print_deposit_arg (`Raw "tru1HdK6HiR31Xo1bSAr4mwwCek8ExgwuUeHm") (`Raw "2") + in + let fee = Test_tez.of_int 10 in + Op.transaction ~fee (I i) account contract Tez.zero ~parameters >>=? fun op -> + Incremental.add_operation + i + op + ~expect_failure: + (check_proto_error (function + | Script_interpreter.Runtime_contract_error _ -> true + | _ -> false)) + >>=? fun _ -> return_unit + +(** [test_invalid_deposit_not_contract] checks a smart contract cannot + deposit something that is not a ticket. *) +let test_invalid_deposit_not_ticket () = + let (_, _, pkh) = gen_l2_account () in + + context_init 1 >>=? fun (b, contracts) -> + let account = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 0 + in + originate b account >>=? fun (b, tx_rollup) -> + Contract_helpers.originate_contract + "contracts/tx_rollup_deposit_incorrect_param.tz" + "Unit" + account + b + (is_implicit_exn account) + >>=? fun (contract, b) -> + Incremental.begin_construction b >>=? fun i -> + let parameters = print_deposit_arg (`Typed tx_rollup) (`Hash pkh) in + let fee = Test_tez.of_int 10 in + Op.transaction ~fee (I i) account contract Tez.zero ~parameters >>=? fun op -> + Incremental.add_operation + i + op + ~expect_failure: + (check_proto_error (function + | Script_interpreter.Bad_contract_parameter _ -> true + | _ -> false)) + >>=? fun _ -> return_unit + +(** [test_invalid_entrypoint] checks that a transaction to an invalid entrypoint + of a transaction rollup fails. *) +let test_invalid_entrypoint () = + let (_, _, pkh) = gen_l2_account () in + + context_init 1 >>=? fun (b, contracts) -> + let account = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 0 + in + originate b account >>=? fun (b, tx_rollup) -> + Contract_helpers.originate_contract + "contracts/tx_rollup_deposit_incorrect_param.tz" + "Unit" + account + b + (is_implicit_exn account) + >>=? fun (contract, b) -> + Incremental.begin_construction b >>=? fun i -> + let parameters = print_deposit_arg (`Typed tx_rollup) (`Hash pkh) in + let fee = Test_tez.of_int 10 in + Op.transaction ~fee (I i) account contract Tez.zero ~parameters >>=? fun op -> + Incremental.add_operation + i + op + ~expect_failure: + (check_proto_error (function + | Script_interpreter.Bad_contract_parameter _ -> true + | _ -> false)) + >>=? fun _ -> return_unit + +(** [test_invalid_l2_address] checks that a smart contract cannot make + a deposit order to something that is not a valid layer-2 address. *) +let test_invalid_l2_address () = + context_init 1 >>=? fun (b, contracts) -> + let account = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 0 + in + originate b account >>=? fun (b, tx_rollup) -> + Contract_helpers.originate_contract + "contracts/tx_rollup_deposit.tz" + "Unit" + account + b + (is_implicit_exn account) + >>=? fun (contract, b) -> + Incremental.begin_construction b >>=? fun i -> + let parameters = + print_deposit_arg (`Typed tx_rollup) (`Raw "\"invalid L2 address\"") + in + let fee = Test_tez.of_int 10 in + Op.transaction ~fee (I i) account contract Tez.zero ~parameters >>=? fun op -> + Incremental.add_operation + i + op + ~expect_failure: + (check_proto_error (function + | Script_interpreter.Bad_contract_parameter _ -> true + | _ -> false)) + >>=? fun _ -> return_unit + +(** [test_valid_deposit_invalid_amount] checks that a transaction to a + transaction rollup fails if the [amount] parameter is not null. *) +let test_valid_deposit_invalid_amount () = + let (_, _, pkh) = gen_l2_account () in + + context_init 1 >>=? fun (b, contracts) -> + let account = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 0 + in + originate b account >>=? fun (b, tx_rollup) -> + Contract_helpers.originate_contract + "contracts/tx_rollup_deposit_one_mutez.tz" + "Unit" + account + b + (is_implicit_exn account) + >>=? fun (contract, b) -> + Incremental.begin_construction b >>=? fun i -> + let parameters = print_deposit_arg (`Typed tx_rollup) (`Hash pkh) in + let fee = Test_tez.of_int 10 in + Op.transaction ~fee (I i) account contract Tez.zero ~parameters >>=? fun op -> + Incremental.add_operation + i + op + ~expect_failure: + (check_proto_error (function + | Apply.Tx_rollup_invalid_transaction_amount -> true + | _ -> false)) + >>=? fun _ -> return_unit + +(** [test_deposit_by_non_internal_operation] checks that a transaction + to the deposit entrypoint of a transaction rollup fails if it is + not internal. *) +let test_deposit_by_non_internal_operation () = + context_init 1 >>=? fun (b, contracts) -> + let account = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 0 + in + originate b account >>=? fun (b, tx_rollup) -> + Op.unsafe_transaction (B b) account (Tx_rollup tx_rollup) Tez.zero + >>=? fun operation -> + Incremental.begin_construction b >>=? fun i -> + Incremental.add_operation i operation ~expect_failure:(function + | Environment.Ecoproto_error + (Apply.Tx_rollup_non_internal_transaction as e) + :: _ -> + Assert.test_error_encodings e ; + return_unit + | _ -> failwith "It should not be possible to send a rollup_operation ") + >>=? fun _i -> return_unit + +(** Test that block finalization changes gas rates *) let test_finalization () = context_init 2 >>=? fun (b, contracts) -> let filler = WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 0 in @@ -505,6 +854,1242 @@ let test_inbox_linked_list () = Assert.is_none ~loc:__LOC__ ~pp:Raw_level.pp before >>=? fun () -> assert_level_equals ~loc:__LOC__ (raw_level 4l) after >>=? fun () -> return () +(** [test_commitments] originates a rollup, and makes a commitment. + It attempts to have a second contract make the same commitment, and + ensures that this fails (and the second contract is not + charged). *) +let test_commitments () = + context_init 2 >>=? fun (b, contracts) -> + let contract1 = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 0 + in + let contract2 = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 1 + in + originate b contract1 >>=? fun (b, tx_rollup) -> + Context.Contract.balance (B b) contract1 >>=? fun balance -> + Context.Contract.balance (B b) contract2 >>=? fun balance2 -> + (* In order to have a permissible commitment, we need a transaction. *) + let contents = "batch" in + Op.tx_rollup_submit_batch (B b) contract1 tx_rollup contents + >>=? fun operation -> + Block.bake ~operation b >>=? fun b -> + Incremental.begin_construction b >>=? fun i -> + wrap (Delegate.find (Incremental.alpha_ctxt i) contract1) >>=? function + | None -> assert false + | Some delegate1 -> + wrap (Delegate.full_balance (Incremental.alpha_ctxt i) delegate1) + >>=? fun initial_full_balance -> + let level_opt = + Raw_level.pred (Level.current (Incremental.alpha_ctxt i)).level + in + let level = + match level_opt with None -> assert false | Some level -> level + in + let batches : Tx_rollup_commitments.Commitment.batch_commitment list = + [{effects = []; root = Bytes.make 20 '0'}] + in + let commitment : Tx_rollup_commitments.Commitment.t = + {level; batches; predecessor = None} + in + let submitted_level = (Level.current (Incremental.alpha_ctxt i)).level in + Op.tx_rollup_commit (I i) contract1 tx_rollup commitment >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + let cost = Tez.of_mutez_exn 10_000_000_000L in + Assert.balance_was_debited ~loc:__LOC__ (I i) contract1 balance cost + >>= fun _ -> + (* Successfully fail to submit a duplicate commitment *) + Op.tx_rollup_commit (I i) contract2 tx_rollup commitment >>=? fun op -> + Incremental.add_operation i op ~expect_failure:(function + | Environment.Ecoproto_error + (Tx_rollup_commitments.Commitment_hash_already_submitted as e) + :: _ -> + Assert.test_error_encodings e ; + return_unit + | t -> failwith "Unexpected error: %a" Error_monad.pp_print_trace t) + >>=? fun i -> + let batches2 : Tx_rollup_commitments.Commitment.batch_commitment list = + [{root = Bytes.make 20 '1'; effects = []}] + in + let commitment2 : Tx_rollup_commitments.Commitment.t = + {level; batches = batches2; predecessor = None} + in + (* Successfully fail to submit a different commitment from contract1 *) + Op.tx_rollup_commit (I i) contract1 tx_rollup commitment2 >>=? fun op -> + Incremental.add_operation i op ~expect_failure:(function + | Environment.Ecoproto_error + (Tx_rollup_commitments.Two_commitments_from_one_committer as e) + :: _ -> + Assert.test_error_encodings e ; + return_unit + | t -> failwith "Unexpected error: %a" Error_monad.pp_print_trace t) + >>=? fun i -> + let batches3 : Tx_rollup_commitments.Commitment.batch_commitment list = + [ + {root = Bytes.make 20 '1'; effects = []}; + {root = Bytes.make 20 '2'; effects = []}; + ] + in + let commitment3 : Tx_rollup_commitments.Commitment.t = + {level; batches = batches3; predecessor = None} + in + (* Successfully fail to submit a different commitment from contract2 *) + Op.tx_rollup_commit (I i) contract2 tx_rollup commitment3 >>=? fun op -> + Incremental.add_operation i op ~expect_failure:(function + | Environment.Ecoproto_error + (Tx_rollup_commitments.Wrong_batch_count as e) + :: _ -> + Assert.test_error_encodings e ; + return_unit + | t -> failwith "Unexpected error: %a" Error_monad.pp_print_trace t) + >>=? fun i -> + (* No charge. *) + Assert.balance_was_debited ~loc:__LOC__ (I i) contract2 balance2 Tez.zero + >>=? fun () -> + let ctxt = Incremental.alpha_ctxt i in + wrap (Tx_rollup_commitments.get_commitments ctxt tx_rollup level) + >>=? fun (ctxt, commitments) -> + (Alcotest.( + check int "Expected one commitment" 1 (List.length commitments)) ; + let expected_hash = Tx_rollup_commitments.Commitment.hash commitment in + match List.nth commitments 0 with + | None -> assert false + | Some {hash; committer; submitted_at; _} -> + Alcotest.( + check commitment_hash_testable "Commitment hash" expected_hash hash) ; + + Alcotest.(check contract_testable "Committer" contract1 committer) ; + + Alcotest.( + check raw_level_testable "Submitted" submitted_level submitted_at) ; + return ()) + >>=? fun () -> + check_bond ctxt tx_rollup contract1 1 1 >>=? fun () -> + check_bond ctxt tx_rollup contract2 0 0 >>=? fun () -> + wrap (Delegate.full_balance ctxt delegate1) >>=? fun full_balance -> + Assert.equal_tez ~loc:__LOC__ initial_full_balance full_balance + >>=? fun () -> + ignore i ; + return () + +let make_transactions_in tx_rollup contract blocks b = + let contents = "batch " in + let rec aux cur blocks b = + match blocks with + | [] -> return b + | hd :: rest when hd = cur -> + Op.tx_rollup_submit_batch (B b) contract tx_rollup contents + >>=? fun operation -> + Block.bake ~operation b >>=? fun b -> aux (cur + 1) rest b + | blocks -> + let operations = [] in + Block.bake ~operations b >>=? fun b -> aux (cur + 1) blocks b + in + aux 2 blocks b + +(** [test_commitment_predecessor] tests commitment predecessor edge cases *) +let test_commitment_predecessor () = + context_init 1 >>=? fun (b, contracts) -> + let contract1 = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 0 + in + originate b contract1 >>=? fun (b, tx_rollup) -> + (* Transactions in blocks 2, 3, 6 *) + make_transactions_in tx_rollup contract1 [2; 3; 6] b >>=? fun b -> + Incremental.begin_construction b >>=? fun i -> + (* Check error: Commitment with predecessor for first block *) + let batches : Tx_rollup_commitments.Commitment.batch_commitment list = + [{effects = []; root = Bytes.make 20 '0'}] + in + let some_hash = + Tx_rollup_commitments.Commitment_hash.of_bytes_exn + (Bytes.of_string "tcu1deadbeefdeadbeefdeadbeefdead") + in + let commitment : Tx_rollup_commitments.Commitment.t = + {level = raw_level 1l; batches; predecessor = Some some_hash} + in + Op.tx_rollup_commit (I i) contract1 tx_rollup commitment >>=? fun op -> + let error = + Tx_rollup_inbox.Tx_rollup_inbox_does_not_exist (tx_rollup, raw_level 1l) + in + Incremental.add_operation i op ~expect_failure:(function + | Environment.Ecoproto_error e :: _ when e = error -> + Assert.test_error_encodings error ; + return_unit + | _ -> failwith "Need to check commitment predecessor") + >>=? fun i -> + (* Commitment without predecessor for block with predecessor*) + let commitment : Tx_rollup_commitments.Commitment.t = + {level = raw_level 3l; batches; predecessor = None} + in + Op.tx_rollup_commit (I i) contract1 tx_rollup commitment >>=? fun op -> + Incremental.add_operation i op ~expect_failure:(function + | Environment.Ecoproto_error + (Tx_rollup_commitments.Wrong_commitment_predecessor_level as e) + :: _ -> + Assert.test_error_encodings e ; + return_unit + | _ -> failwith "Need to check commitment predecessor") + >>=? fun i -> + (* Commitment refers to a predecessor which does not exist *) + let commitment : Tx_rollup_commitments.Commitment.t = + {level = raw_level 3l; batches; predecessor = Some some_hash} + in + Op.tx_rollup_commit (I i) contract1 tx_rollup commitment >>=? fun op -> + Incremental.add_operation i op ~expect_failure:(function + | Environment.Ecoproto_error + (Tx_rollup_commitments.Missing_commitment_predecessor as e) + :: _ -> + Assert.test_error_encodings e ; + return_unit + | _ -> failwith "Need to check commitment predecessor") + >>=? fun i -> + (* Try to commit to an empty level between full ones *) + let commitment : Tx_rollup_commitments.Commitment.t = + {level = raw_level 5l; batches; predecessor = Some some_hash} + in + Op.tx_rollup_commit (I i) contract1 tx_rollup commitment >>=? fun op -> + let error = + Tx_rollup_inbox.Tx_rollup_inbox_does_not_exist (tx_rollup, raw_level 5l) + in + Incremental.add_operation i op ~expect_failure:(function + | Environment.Ecoproto_error e :: _ when e = error -> + Assert.test_error_encodings e ; + return_unit + | _ -> failwith "Need to check for skipped levels") + >>=? fun i -> + ignore i ; + return () + +(** [test_commitment_retire_simple] tests commitment retirement simple cases. + Note that it manually retires commitments rather than waiting for them to + age out. *) +let test_commitment_retire_simple () = + context_init 1 >>=? fun (b, contracts) -> + let contract1 = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 0 + in + originate b contract1 >>=? fun (b, tx_rollup) -> + (* In order to have a permissible commitment, we need a transaction. *) + let contents = "batch" in + Op.tx_rollup_submit_batch (B b) contract1 tx_rollup contents + >>=? fun operation -> + Block.bake ~operation b >>=? fun b -> + Incremental.begin_construction b >>=? fun i -> + let level_opt = + Raw_level.pred (Level.current (Incremental.alpha_ctxt i)).level + in + let level = + match level_opt with None -> assert false | Some level -> level + in + (* Test retirement with no commitment *) + wrap + (Tx_rollup_commitments.Internal_for_tests.retire_rollup_level + (Incremental.alpha_ctxt i) + tx_rollup + level + (raw_level @@ Incremental.level i)) + >>=? fun (_ctxt, retired) -> + assert (not retired) ; + (* Now, make a commitment *) + let batches : Tx_rollup_commitments.Commitment.batch_commitment list = + [{effects = []; root = Bytes.make 20 '0'}] + in + let commitment : Tx_rollup_commitments.Commitment.t = + {level; batches; predecessor = None} + in + Op.tx_rollup_commit (I i) contract1 tx_rollup commitment >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + wrap + (Tx_rollup_commitments.pending_bonded_commitments + (Incremental.alpha_ctxt i) + tx_rollup + contract1) + >>=? fun (_, pending) -> + Alcotest.(check int "One pending commitment" 1 pending) ; + (* We can retire this level *) + wrap + (Tx_rollup_commitments.Internal_for_tests.retire_rollup_level + (Incremental.alpha_ctxt i) + tx_rollup + level + (Level.current (Incremental.alpha_ctxt i)).level) + >>=? fun (ctxt, retired) -> + assert retired ; + check_bond ctxt tx_rollup contract1 0 1 >>=? fun () -> + ignore i ; + return () + +(** [test_commitment_retire_complex] tests a complicated commitment + retirement scenario: + + We have inboxes at 2, 3, and 6. + + - A: Contract 1 commits to 2. + - B: Contract 2 commits to 2 (after 1; this commitment is + necessarily bogus, but we will assume that nobody notices) + - C: Contract 2 commits to 3 (atop A). + - D: Contract 1 commits to 3 (atop bogus commit B) + - E: Contract 2 commits to 3 (atop D). + - F: Contract 1 commits to 6 (atop C). + + So now we retire 2. We want nobody to get a bond back. Then we + retire 3, which will enable 2 to get their bond back. Then we + retire 6, which lets Contract 1 get its bond back. +*) +let test_commitment_retire_complex () = + context_init 2 >>=? fun (b, contracts) -> + let contract1 = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 0 + in + let contract2 = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 1 + in + originate b contract1 >>=? fun (b, tx_rollup) -> + (* Transactions in blocks 2, 3, 6 *) + make_transactions_in tx_rollup contract1 [2; 3; 6] b >>=? fun b -> + Incremental.begin_construction b >>=? fun i -> + let batches : Tx_rollup_commitments.Commitment.batch_commitment list = + [{effects = []; root = Bytes.make 20 '0'}] + in + let commitment_a : Tx_rollup_commitments.Commitment.t = + {level = raw_level 2l; batches; predecessor = None} + in + Op.tx_rollup_commit (I i) contract1 tx_rollup commitment_a >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + let commitment_b : Tx_rollup_commitments.Commitment.t = + {level = raw_level 2l; batches; predecessor = None} + in + Op.tx_rollup_commit (I i) contract2 tx_rollup commitment_b >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + let predecessor = Tx_rollup_commitments.Commitment.hash commitment_a in + let commitment_c : Tx_rollup_commitments.Commitment.t = + {level = raw_level 3l; batches; predecessor = Some predecessor} + in + Op.tx_rollup_commit (I i) contract2 tx_rollup commitment_c >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + let predecessor = Tx_rollup_commitments.Commitment.hash commitment_b in + + let commitment_d : Tx_rollup_commitments.Commitment.t = + {level = raw_level 3l; batches; predecessor = Some predecessor} + in + Op.tx_rollup_commit (I i) contract2 tx_rollup commitment_d >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + let predecessor = Tx_rollup_commitments.Commitment.hash commitment_d in + + let commitment_e : Tx_rollup_commitments.Commitment.t = + {level = raw_level 6l; batches; predecessor = Some predecessor} + in + Op.tx_rollup_commit (I i) contract2 tx_rollup commitment_e >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + let predecessor = Tx_rollup_commitments.Commitment.hash commitment_c in + let commitment_f : Tx_rollup_commitments.Commitment.t = + {level = raw_level 3l; batches; predecessor = Some predecessor} + in + Op.tx_rollup_commit (I i) contract2 tx_rollup commitment_f >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + wrap + (Tx_rollup_commitments.Internal_for_tests.retire_rollup_level + (Incremental.alpha_ctxt i) + tx_rollup + (raw_level 2l) + (raw_level 2l)) + >>=? fun (ctxt, retired) -> + assert retired ; + check_bond ctxt tx_rollup contract1 3 1 >>=? fun () -> + check_bond ctxt tx_rollup contract2 3 1 >>=? fun () -> + wrap + (Tx_rollup_commitments.Internal_for_tests.retire_rollup_level + ctxt + tx_rollup + (raw_level 3l) + (raw_level 3l)) + >>=? fun (ctxt, retired) -> + assert retired ; + check_bond ctxt tx_rollup contract1 3 1 >>=? fun () -> + check_bond ctxt tx_rollup contract2 0 0 >>=? fun () -> + wrap + (Tx_rollup_commitments.Internal_for_tests.retire_rollup_level + ctxt + tx_rollup + (raw_level 6l) + (raw_level 6l)) + >>=? fun (ctxt, retired) -> + assert retired ; + check_bond ctxt tx_rollup contract1 0 0 >>=? fun () -> + check_bond ctxt tx_rollup contract2 0 0 >>=? fun () -> + ignore ctxt ; + ignore i ; + return () + +(** [test_rejection_propagation] tests a full rejection propagation: A commitment + by c1 is rejected, meaning that a future commitment by c2 is + rejected, meaning that a *past* commitment by c2 is rejected (by + "dead bond" rule), meaning that a later commitment by C3 is + rejectect (by "dead parent" rule) +- A: Contract 1 commits to 2 (this will be rejected) +- B: Contract 2 commits to 2 (this will *later* be rejected) +- C: Contract 2 commits to 3 (atop A). +- D: Contract 3 commits to 3 (atop B) +- E: Contract 4 commits to 2 (this will survive) +- F: Contract 4 commits to 3 (atop E; this will survive too) +*) +let test_rejection_propagation () = + context_init 4 >>=? fun (b, contracts) -> + let contract1 = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 0 + in + let contract2 = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 1 + in + let contract3 = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 2 + in + let contract4 = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 3 + in + originate b contract1 >>=? fun (b, tx_rollup) -> + make_transactions_in tx_rollup contract1 [2; 3] b >>=? fun b -> + Incremental.begin_construction b >>=? fun i -> + let batches1 : Tx_rollup_commitments.Commitment.batch_commitment list = + [{effects = []; root = Bytes.make 20 '0'}] + in + let batches2 : Tx_rollup_commitments.Commitment.batch_commitment list = + [{effects = []; root = Bytes.make 20 '1'}] + in + let batches3 : Tx_rollup_commitments.Commitment.batch_commitment list = + [{effects = []; root = Bytes.make 20 '2'}] + in + let commitment_a : Tx_rollup_commitments.Commitment.t = + {level = raw_level 2l; batches = batches1; predecessor = None} + in + Op.tx_rollup_commit (I i) contract1 tx_rollup commitment_a >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + let commitment_b : Tx_rollup_commitments.Commitment.t = + {level = raw_level 2l; batches = batches2; predecessor = None} + in + Op.tx_rollup_commit (I i) contract2 tx_rollup commitment_b >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + let predecessor = Tx_rollup_commitments.Commitment.hash commitment_a in + + let commitment_c : Tx_rollup_commitments.Commitment.t = + {level = raw_level 3l; batches = batches1; predecessor = Some predecessor} + in + Op.tx_rollup_commit (I i) contract2 tx_rollup commitment_c >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + let predecessor = Tx_rollup_commitments.Commitment.hash commitment_b in + + let commitment_d : Tx_rollup_commitments.Commitment.t = + {level = raw_level 3l; batches = batches2; predecessor = Some predecessor} + in + Op.tx_rollup_commit (I i) contract3 tx_rollup commitment_d >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + Incremental.finalize_block i >>=? fun b -> + Incremental.begin_construction b >>=? fun i -> + let commitment_e : Tx_rollup_commitments.Commitment.t = + {level = raw_level 2l; batches = batches3; predecessor = None} + in + Op.tx_rollup_commit (I i) contract4 tx_rollup commitment_e >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + let predecessor = Tx_rollup_commitments.Commitment.hash commitment_e in + + let commitment_f : Tx_rollup_commitments.Commitment.t = + {level = raw_level 3l; batches = batches3; predecessor = Some predecessor} + in + Op.tx_rollup_commit (I i) contract4 tx_rollup commitment_f >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + wrap + (Tx_rollup_commitments.reject_commitment + (Incremental.alpha_ctxt i) + tx_rollup + (raw_level 2l) + (Tx_rollup_commitments.Commitment.hash commitment_a) + contract4 + Z.one) + >>=? fun ctxt -> + check_bond ctxt tx_rollup contract1 0 1 >>=? fun () -> + check_bond ctxt tx_rollup contract2 0 1 >>=? fun () -> + check_bond ctxt tx_rollup contract3 0 1 >>=? fun () -> + check_bond ctxt tx_rollup contract4 2 1 >>=? fun () -> + ignore ctxt ; + ignore i ; + return () + +(** [test_commitment_acceptance] tests a case where there are multiple + nonrejected commitments at finalization time. +- A: Contract 1 commits to 2 (this will be accepted) +- B: Contract 2 commits to 2 (this will removed but not rejected) +- C: Contract 2 commits to 3 (atop A). +- D: Contract 3 commits to 3 (atop B, to be removed) +*) +let test_commitment_acceptance () = + context_init 4 >>=? fun (b, contracts) -> + let contract1 = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 0 + in + let contract2 = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 1 + in + let contract3 = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 2 + in + let contract4 = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 3 + in + originate b contract1 >>=? fun (b, tx_rollup) -> + make_transactions_in tx_rollup contract1 [2; 3] b >>=? fun b -> + Incremental.begin_construction b >>=? fun i -> + let batches1 : Tx_rollup_commitments.Commitment.batch_commitment list = + [{effects = []; root = Bytes.make 20 '0'}] + in + let batches2 : Tx_rollup_commitments.Commitment.batch_commitment list = + [{effects = []; root = Bytes.make 20 '1'}] + in + let batches3 : Tx_rollup_commitments.Commitment.batch_commitment list = + [{effects = []; root = Bytes.make 20 '2'}] + in + let commitment_a : Tx_rollup_commitments.Commitment.t = + {level = raw_level 2l; batches = batches1; predecessor = None} + in + Op.tx_rollup_commit (I i) contract1 tx_rollup commitment_a >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + let commitment_b : Tx_rollup_commitments.Commitment.t = + {level = raw_level 2l; batches = batches2; predecessor = None} + in + Op.tx_rollup_commit (I i) contract2 tx_rollup commitment_b >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + let predecessor = Tx_rollup_commitments.Commitment.hash commitment_a in + let commitment_c : Tx_rollup_commitments.Commitment.t = + {level = raw_level 3l; batches = batches1; predecessor = Some predecessor} + in + Op.tx_rollup_commit (I i) contract2 tx_rollup commitment_c >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + let predecessor = Tx_rollup_commitments.Commitment.hash commitment_b in + let commitment_d : Tx_rollup_commitments.Commitment.t = + {level = raw_level 3l; batches = batches2; predecessor = Some predecessor} + in + Op.tx_rollup_commit (I i) contract3 tx_rollup commitment_d >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + Incremental.finalize_block i >>=? fun b -> + Incremental.begin_construction b >>=? fun i -> + let cur = Incremental.level i in + bake_until i (Int32.add cur 30l) >>=? fun i -> + Incremental.finalize_block i >>=? fun b -> + let contents = "batch" in + Op.tx_rollup_submit_batch (B b) contract1 tx_rollup contents >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + let pred = commitment_c in + let predecessor = Tx_rollup_commitments.Commitment.hash pred in + let level = Int32.add (Incremental.level i) 1l in + let commitment : Tx_rollup_commitments.Commitment.t = + { + level = raw_level level; + batches = batches3; + predecessor = Some predecessor; + } + in + Op.tx_rollup_commit (I i) contract4 tx_rollup commitment >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + let ctxt = Incremental.alpha_ctxt i in + check_bond ctxt tx_rollup contract1 0 1 >>=? fun () -> + check_bond ctxt tx_rollup contract2 0 1 >>=? fun () -> + check_bond ctxt tx_rollup contract3 0 1 >>=? fun () -> + check_bond ctxt tx_rollup contract4 1 1 >>=? fun () -> + ignore ctxt ; + ignore i ; + return () + +(** [test_bond_finalization] tests that commitment operations + in fact finalize bonds. *) +let test_bond_finalization () = + context_init 2 >>=? fun (b, contracts) -> + let contract1 = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 0 + in + let contract2 = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 1 + in + originate b contract1 >>=? fun (b, tx_rollup) -> + (* Transactions in block 2 *) + make_transactions_in tx_rollup contract1 [2] b >>=? fun b -> + Incremental.begin_construction b >>=? fun i -> + Op.tx_rollup_return_bond (I i) contract1 tx_rollup >>=? fun op -> + Incremental.add_operation i op ~expect_failure:(function + | Environment.Ecoproto_error + (Tx_rollup_commitments.Bond_does_not_exist a_contract1 as e) + :: _ + when a_contract1 = contract1 -> + Assert.test_error_encodings e ; + return_unit + | _ -> failwith "Commitment bond should not exist yet") + >>=? fun i -> + let batches : Tx_rollup_commitments.Commitment.batch_commitment list = + [{effects = []; root = Bytes.make 20 '0'}] + in + let commitment_a : Tx_rollup_commitments.Commitment.t = + {level = raw_level 2l; batches; predecessor = None} + in + Op.tx_rollup_commit (I i) contract1 tx_rollup commitment_a >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + let contents = "batch" in + (* Here, we create new inboxes and commitments (we need the inboxes + so that the commitments can be created. All of this is done by + contract2 so that contract1's bond can be returned. *) + let rec bake_n n top i pred = + if n >= top then return (pred, i) + else + Incremental.finalize_block i >>=? fun b -> + Incremental.begin_construction b >>=? fun i -> + Op.tx_rollup_submit_batch (B b) contract1 tx_rollup contents + >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + let predecessor = Tx_rollup_commitments.Commitment.hash pred in + let commitment : Tx_rollup_commitments.Commitment.t = + { + level = raw_level (Int32.of_int n); + batches; + predecessor = Some predecessor; + } + in + Op.tx_rollup_commit (I i) contract2 tx_rollup commitment >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + bake_n (n + 1) top i commitment + in + (* Still fails after 29 blocks..*) + bake_n 4 33 i commitment_a >>=? fun (last_commitment, i) -> + Op.tx_rollup_return_bond (I i) contract1 tx_rollup >>=? fun op -> + Incremental.add_operation i op ~expect_failure:(function + | Environment.Ecoproto_error + (Tx_rollup_commitments.Bond_in_use a_contract1 as e) + :: _ + when a_contract1 = contract1 -> + Assert.test_error_encodings e ; + return_unit + | _ -> failwith "Need to check that bond is in-use ") + >>=? fun i -> + (* But passes after the 30th.. *) + bake_n 33 34 i last_commitment >>=? fun (_, i) -> + Op.tx_rollup_return_bond (I i) contract1 tx_rollup >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + (* Here, the bond is fully returned. *) + check_bond (Incremental.alpha_ctxt i) tx_rollup contract1 0 0 >>=? fun () -> + ignore i ; + return () + +(** [test_rejection] tests that rejection works. *) +let test_rejection () = + context_init 1 >>=? fun (b, contracts) -> + let contract1 = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 0 + in + originate b contract1 >>=? fun (b, tx_rollup) -> + (* Transactions in block 2 *) + make_transactions_in tx_rollup contract1 [2] b >>=? fun b -> + Incremental.begin_construction b >>=? fun i -> + let batches : Tx_rollup_commitments.Commitment.batch_commitment list = + [{root = Bytes.empty; effects = []}] + in + (* "Random" numbers *) + let nonce = 1000L in + let nonce2 = 1001L in + wrap (Lwt.return @@ Tx_rollup_message.make_batch (Incremental.alpha_ctxt i) "") + >>=? fun (batch, _) -> + let commitment : Tx_rollup_commitments.Commitment.t = + {level = raw_level 2l; batches; predecessor = None} + in + Op.tx_rollup_commit (I i) contract1 tx_rollup commitment >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + let hash = Tx_rollup_commitments.Commitment.hash commitment in + (* Test missing prerejection *) + Op.tx_rollup_reject + (I i) + contract1 + tx_rollup + (raw_level 2l) + hash + 1 + batch + nonce + >>=? fun op -> + Incremental.add_operation i op ~expect_failure:(function + | Environment.Ecoproto_error + (Tx_rollup_rejection.Rejection_without_prerejection as e) + :: _ -> + Assert.test_error_encodings e ; + return_unit + | _ -> failwith "Need to check prerejection") + >>=? fun i -> + Op.tx_rollup_prereject (I i) contract1 tx_rollup (raw_level 2l) hash 0 nonce + >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + (* need to bake after prereject *) + Incremental.finalize_block i >>=? fun b -> + Incremental.begin_construction b >>=? fun i -> + (* Correct rejection *) + Op.tx_rollup_reject + (I i) + contract1 + tx_rollup + (raw_level 2l) + hash + 0 + batch + nonce + >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + (* Right commitment *) + let batches : Tx_rollup_commitments.Commitment.batch_commitment list = + [{root = Bytes.make 20 '0'; effects = []}] + in + let correct_commitment : Tx_rollup_commitments.Commitment.t = + {level = raw_level 2l; batches; predecessor = None} + in + Op.tx_rollup_commit (I i) contract1 tx_rollup correct_commitment + >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + let hash = Tx_rollup_commitments.Commitment.hash correct_commitment in + Op.tx_rollup_prereject (I i) contract1 tx_rollup (raw_level 2l) hash 0 nonce2 + >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + Incremental.finalize_block i >>=? fun b -> + Incremental.begin_construction b >>=? fun i -> + Op.tx_rollup_reject + (I i) + contract1 + tx_rollup + (raw_level 2l) + hash + 0 + batch + nonce2 + >>=? fun op -> + (* Wrong rejection *) + Incremental.add_operation i op ~expect_failure:(function + | Environment.Ecoproto_error (Tx_rollup_rejection.Wrong_rejection as e) + :: _ -> + Assert.test_error_encodings e ; + return_unit + | _ -> failwith "Should not reject correct commitments") + >>=? fun i -> + ignore i ; + return () + +(** [test_all_commitments_rejected] tests the case where all commitments + have been rejected as-of finalization time, so that there is nothing + to finalize. We want to ensure that we can later go back and finalize + that level. *) +let test_all_commitments_rejected () = + context_init 2 >>=? fun (b, contracts) -> + let contract1 = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 0 + in + let contract2 = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 1 + in + + originate b contract1 >>=? fun (b, tx_rollup) -> + (* Transactions in block 2,3, and 6 *) + make_transactions_in tx_rollup contract1 [2; 3; 6] b >>=? fun b -> + Incremental.begin_construction b >>=? fun i -> + let batches : Tx_rollup_commitments.Commitment.batch_commitment list = + [ + {effects = []; root = Bytes.make 20 '0'} + ] + in + let good_commitment : Tx_rollup_commitments.Commitment.t = + {level = raw_level 2l; batches; predecessor = None} + in + Op.tx_rollup_commit (I i) contract2 tx_rollup good_commitment >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + let nonce = 1000L in + wrap (Lwt.return @@ Tx_rollup_message.make_batch (Incremental.alpha_ctxt i) "") + >>=? fun (batch, _) -> + let good_hash = Tx_rollup_commitments.Commitment.hash good_commitment in + let bad_commitment : Tx_rollup_commitments.Commitment.t = + {level = raw_level 3l; batches; predecessor = Some good_hash} + in + Op.tx_rollup_commit (I i) contract1 tx_rollup bad_commitment >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + let bad_hash = Tx_rollup_commitments.Commitment.hash bad_commitment in + Op.tx_rollup_prereject + (I i) + contract1 + tx_rollup + (raw_level 3l) + bad_hash + 0 + nonce + >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + (* need to bake after prereject *) + Incremental.finalize_block i >>=? fun b -> + Incremental.begin_construction b >>=? fun i -> + Op.tx_rollup_reject + (I i) + contract1 + tx_rollup + (raw_level 3l) + bad_hash + 0 + batch + nonce + >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + (* Now bake until we can go past the point at which we could + have finalized the bad commitment if it hadn't been rejected *) + bake_until i (Int32.add (Incremental.level i) 30l) >>=? fun i -> + wrap + (Tx_rollup_state.first_unfinalized_level + (Incremental.alpha_ctxt i) + tx_rollup) + >>=? fun (_, level) -> + Alcotest.( + check + (option raw_level_testable) + "Because no commitments have been submitted, the first unfinalized level \ + is the first-submitted level" + (Some (raw_level 2l)) + level) ; + let commitment : Tx_rollup_commitments.Commitment.t = + {level = raw_level 3l; batches; predecessor = Some good_hash} + in + Op.tx_rollup_commit (I i) contract1 tx_rollup commitment >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + (* This should have finalized level 2, but not yet level 3 *) + wrap + (Tx_rollup_state.first_unfinalized_level + (Incremental.alpha_ctxt i) + tx_rollup) + >>=? fun (_, level) -> + Alcotest.( + check + (option raw_level_testable) + "Expected level 3 to be unfinalized" + (Some (raw_level 3l)) + level) ; + + (* Now level 3 has a real commitment -- will it get finalized? *) + bake_until i (Int32.add (Incremental.level i) 30l) >>=? fun i -> + let predecessor = Tx_rollup_commitments.Commitment.hash commitment in + let commitment : Tx_rollup_commitments.Commitment.t = + {level = raw_level 6l; batches; predecessor = Some predecessor} + in + Op.tx_rollup_commit (I i) contract1 tx_rollup commitment >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + wrap + (Tx_rollup_state.first_unfinalized_level + (Incremental.alpha_ctxt i) + tx_rollup) + >>=? fun (_, level) -> + Alcotest.( + check + (option raw_level_testable) + "Expected level 6 to be unfinalized" + (Some (raw_level 6l)) + level) ; + + return () + +(* [test_rejection_reward] tests that rejection rewards are (a) awarded at + finalization time, and (b) go to the contract with the first prerejetion. + The scenario is: + {ol {li contract1 creates a bad commitment.} + {li contract4 creates a good commitment so that retirement can happen.} + {li contract2 creates a prerejection of this commitment.} + {li contract3 creates a (later) prerejection too.} + {li contract4 creates a (later) prerejection too.} + {li contract3 submits their rejection.} + {li contract2 submits their rejection.} + {li contract4 submits their rejection.} + {li contract5 submits their rejection (in the same block as contract4, + just to ensure that this case works).} + {li enough blocks are baked so that contract5 can submit another + commitment, which kicks off finalization.} + } + + We expect that contract2 will get rewarded, since their prerejection was first + even though contract3's rejection came first. + *) +let test_rejection_reward () = + context_init 5 >>=? fun (b, contracts) -> + let contract1 = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 0 + in + let contract2 = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 1 + in + let contract3 = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 2 + in + let contract4 = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 3 + in + let contract5 = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 4 + in + originate b contract1 >>=? fun (b, tx_rollup) -> + make_transactions_in tx_rollup contract1 [2] b >>=? fun b -> + Incremental.begin_construction b >>=? fun i -> + (* This is the commitment that is going to be rejected *) + let batches : Tx_rollup_commitments.Commitment.batch_commitment list = + [{root = Bytes.empty; effects = []}] + in + let bad_commitment : Tx_rollup_commitments.Commitment.t = + {level = raw_level 2l; batches; predecessor = None} + in + + (* This is the good commitment that we will use later *) + let batches : Tx_rollup_commitments.Commitment.batch_commitment list = + [{root = Bytes.make 20 '0'; effects = []}] + in + let good_commitment : Tx_rollup_commitments.Commitment.t = + {level = raw_level 2l; batches; predecessor = None} + in + (* Submit commitments at level 3 *) + Op.tx_rollup_commit (I i) contract1 tx_rollup bad_commitment >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + Op.tx_rollup_commit (I i) contract4 tx_rollup good_commitment >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + let bad_commitment_hash = + Tx_rollup_commitments.Commitment.hash bad_commitment + in + (* "Random" numbers *) + let nonce = 1000L in + let nonce2 = 1001L in + let nonce3 = 1002L in + wrap (Lwt.return @@ Tx_rollup_message.make_batch (Incremental.alpha_ctxt i) "") + >>=? fun (batch, _) -> + Op.tx_rollup_prereject + (I i) + contract2 + tx_rollup + (raw_level 2l) + bad_commitment_hash + 0 + nonce + >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + (* Finalize to enforce ordering *) + Incremental.finalize_block i >>=? fun b -> + Incremental.begin_construction b >>=? fun i -> + Op.tx_rollup_prereject + (I i) + contract3 + tx_rollup + (raw_level 2l) + bad_commitment_hash + 0 + nonce2 + >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + (* Finalize to enforce ordering *) + Incremental.finalize_block i >>=? fun b -> + Incremental.begin_construction b >>=? fun i -> + Op.tx_rollup_prereject + (I i) + contract4 + tx_rollup + (raw_level 2l) + bad_commitment_hash + 0 + nonce3 + >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + Op.tx_rollup_prereject + (I i) + contract5 + tx_rollup + (raw_level 2l) + bad_commitment_hash + 0 + nonce3 + >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + (* Finalize to enforce ordering *) + Incremental.finalize_block i >>=? fun b -> + Incremental.begin_construction b >>=? fun i -> + Op.tx_rollup_reject + (I i) + contract3 + tx_rollup + (raw_level 2l) + bad_commitment_hash + 0 + batch + nonce2 + >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + (* Finalize to enforce ordering *) + Incremental.finalize_block i >>=? fun b -> + Incremental.begin_construction b >>=? fun i -> + Op.tx_rollup_reject + (I i) + contract2 + tx_rollup + (raw_level 2l) + bad_commitment_hash + 0 + batch + nonce + >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + (* Finalize to enforce ordering *) + Incremental.finalize_block i >>=? fun b -> + Incremental.begin_construction b >>=? fun i -> + Op.tx_rollup_reject + (I i) + contract4 + tx_rollup + (raw_level 2l) + bad_commitment_hash + 0 + batch + nonce3 + >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + Op.tx_rollup_reject + (I i) + contract5 + tx_rollup + (raw_level 2l) + bad_commitment_hash + 0 + batch + nonce3 + >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + bake_until i 33l >>=? fun i -> + (* Now we need one more commitment, so we need a batch *) + Op.tx_rollup_submit_batch (I i) contract4 tx_rollup "contents" >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + Incremental.finalize_block i >>=? fun b -> + Incremental.begin_construction b >>=? fun i -> + let good_commitment_hash = + Tx_rollup_commitments.Commitment.hash good_commitment + in + let predecessor = good_commitment_hash in + let commitment : Tx_rollup_commitments.Commitment.t = + {level = raw_level 34l; batches; predecessor = Some predecessor} + in + Context.Contract.balance (B b) contract2 >>=? fun balance2 -> + Context.Contract.balance (B b) contract3 >>=? fun balance3 -> + Context.Contract.balance (B b) contract4 >>=? fun balance4 -> + Op.tx_rollup_commit (I i) contract5 tx_rollup commitment >>=? fun op -> + Incremental.add_operation i op >>=? fun i -> + let bond = Constants.tx_rollup_commitment_bond (Incremental.alpha_ctxt i) in + wrap (Lwt.return Tez.(bond /? 2L)) >>=? fun bond -> + (* check balances *) + Assert.balance_was_credited ~loc:__LOC__ (I i) contract2 balance2 bond + >>=? fun () -> + Assert.balance_was_credited ~loc:__LOC__ (I i) contract3 balance3 Tez.zero + >>=? fun () -> + Assert.balance_was_debited ~loc:__LOC__ (I i) contract4 balance4 Tez.zero + >>=? fun () -> + ignore i ; + return () + +let test_full_inbox () = + context_init 1 >>=? fun (b, contracts) -> + let contract = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 0 + in + originate b contract >>=? fun (b, tx_rollup) -> + let range start top = + let rec aux n acc = if n < start then acc else aux (n - 1) (n :: acc) in + aux top [] + in + (* Transactions in blocks [2..102) *) + make_transactions_in tx_rollup contract (range 2 102) b >>=? fun b -> + Incremental.begin_construction b >>=? fun i -> + Op.tx_rollup_submit_batch (B b) contract tx_rollup "contents" >>=? fun op -> + Incremental.add_operation i op ~expect_failure:(function + | Environment.Ecoproto_error + (Tx_rollup_commitments.Too_many_unfinalized_levels as e) + :: _ -> + Assert.test_error_encodings e ; + return_unit + | _ -> failwith "Need to avoid too many unfinalized inboxes") + >>=? fun i -> + ignore i ; + return () + +let test_prerejection_gc () = + let make_hash () = + Tx_rollup_commitments.Commitment_hash.of_bytes_exn @@ Bytes.of_string + @@ "tcu1" + ^ String.init 28 (fun _ -> char_of_int (50 + Random.State.int rng_state 8)) + in + let assert_equal_option_z ~loc actual expected = + Assert.equal + ~loc + (Option.equal Z.equal) + "oldest" + (Format.pp_print_option Z.pp_print) + actual + expected + in + let assert_oldest_prerejection ~loc i expected = + wrap + (Tx_rollup_commitments.Internal_for_tests.get_oldest_prerejection + (Incremental.alpha_ctxt i)) + >>=? fun oldest -> assert_equal_option_z ~loc oldest expected + in + + context_init 1 >>=? fun (b, contracts) -> + let contract1 = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 0 + in + originate b contract1 >>=? fun (b, tx_rollup) -> + Incremental.begin_construction b >>=? fun i -> + let nonce = 1L in + let add_prerejection i = + Op.tx_rollup_prereject + (I i) + contract1 + tx_rollup + (raw_level 2l) + (make_hash ()) + 1 + nonce + >>=? fun op -> Incremental.add_operation i op + in + (* First, check that one prerejection can be garbage-collected ... but not immediately *) + add_prerejection i >>=? fun i -> + assert_oldest_prerejection ~loc:__LOC__ i (Some Z.zero) >>=? fun () -> + bake_until i 30l >>=? fun i -> + (* First, check that one prerejection can be garbage-collected ... nor after 29 blocks *) + add_prerejection i >>=? fun i -> + assert_oldest_prerejection ~loc:__LOC__ i (Some Z.zero) >>=? fun () -> + bake_until i 31l >>=? fun i -> + (* prerejections are not automatically garbage-collected... *) + assert_oldest_prerejection ~loc:__LOC__ i (Some Z.zero) >>=? fun () -> + add_prerejection i >>=? fun i -> + (* ... but are on the next prerejection *) + assert_oldest_prerejection ~loc:__LOC__ i (Some Z.one) >>=? fun () -> + Incremental.finalize_block i >>=? fun b -> + Incremental.begin_construction b >>=? fun i -> + (* Now we test that a max of 10 prerejections are garbage-collected. + Sadly, we need to bake during this since we will otherwise run out + of manager operations *) + let rec make_prerejections i n = + if n = 0 then return i + else + add_prerejection i >>=? fun i -> + Incremental.finalize_block i >>=? fun b -> + Incremental.begin_construction b >>=? fun i -> make_prerejections i (n - 1) + in + make_prerejections i 11 >>=? fun i -> + (* Clear out all old prerejections -- we just want these 11 to be in range*) + bake_until i 61l >>=? fun i -> + add_prerejection i >>=? fun i -> + assert_oldest_prerejection ~loc:__LOC__ i (Some (Z.of_int 3)) >>=? fun () -> + bake_until i 73l >>=? fun i -> + add_prerejection i >>=? fun i -> + assert_oldest_prerejection ~loc:__LOC__ i (Some (Z.of_int 13)) >>=? fun () -> + add_prerejection i >>=? fun i -> + assert_oldest_prerejection ~loc:__LOC__ i (Some (Z.of_int 14)) >>=? fun () -> + ignore i ; + return () + +let test_withdraw () = + context_init 2 >>=? fun (b, contracts) -> + let contract1 = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 0 + in + let contract2 = + WithExceptions.Option.get ~loc:__LOC__ @@ List.nth contracts 1 + in + originate b contract1 >>=? fun (b, tx_rollup) -> + Incremental.begin_construction b >>=? fun i -> + let rollup_ticket_hash = + make_unit_ticket_key (Incremental.alpha_ctxt i) contract1 tx_rollup + in + wrap + (Ticket_balance.adjust_balance + (Incremental.alpha_ctxt i) + rollup_ticket_hash + ~delta:(Z.of_int 1000)) + >>=? fun (_counter, ctxt) -> + let open Tezos_micheline.Micheline in + let open Michelson_v1_primitives in + let ticketer = + Bytes (0, Data_encoding.Binary.to_bytes_exn Contract.encoding contract1) + in + let ty = Prim (0, T_unit, [], []) in + let contents = Prim (0, D_Unit, [], []) in + wrap + (Ticket_balance_key.ticket_balance_key_unparsed + ctxt + ~owner:contract1 + ticketer + ty + contents) + >>=? fun (destination_ticket_hash, ctxt) -> + wrap + (Tx_rollup_offramp.add_tickets_to_offramp + ctxt + tx_rollup + contract1 + rollup_ticket_hash + 123L) + >>=? fun ctxt -> + wrap + (Tx_rollup_offramp.withdraw + ctxt + tx_rollup + contract1 + ~rollup_ticket_hash + ~destination_ticket_hash + 100L) + >>=? fun ctxt -> + (* try to withdraw too many *) + (wrap + (Tx_rollup_offramp.withdraw + ctxt + tx_rollup + contract1 + ~rollup_ticket_hash + ~destination_ticket_hash + 24L) + >>= function + | Error _ -> return () + | Ok _ -> assert false) + >>=? fun () -> + (* try to withdraw from wrong account *) + wrap + (Tx_rollup_offramp.withdraw + ctxt + tx_rollup + contract2 + ~rollup_ticket_hash + ~destination_ticket_hash + 23L + >>= function + | Error _ -> return () + | Ok _ -> assert false) + >>=? fun () -> + wrap + (Tx_rollup_offramp.withdraw + ctxt + tx_rollup + contract1 + ~rollup_ticket_hash + ~destination_ticket_hash + 23L) + >>=? fun ctxt -> + wrap (Ticket_balance.get_balance ctxt rollup_ticket_hash) + >>=? fun (balance, ctxt) -> + Alcotest.( + check + (option z_testable) + "Expect a balance of 877" + (Some (Z.of_int 877)) + balance) ; + + ignore ctxt ; + + return () + let tests = [ Tztest.tztest @@ -531,6 +2116,49 @@ let tests = "Try to add several batches to reach the inbox limit" `Quick test_inbox_too_big; + Tztest.tztest "Test deposit with valid contract" `Quick test_valid_deposit; + Tztest.tztest + "Test deposit with invalid parameter" + `Quick + test_invalid_deposit_not_ticket; + Tztest.tztest + "Test valid deposit to inexistant rollup" + `Quick + test_valid_deposit_inexistant_rollup; + Tztest.tztest "Test invalid entrypoint" `Quick test_invalid_entrypoint; + Tztest.tztest + "Test valid deposit to invalid L2 address" + `Quick + test_invalid_l2_address; + Tztest.tztest + "Test valid deposit with non-zero amount" + `Quick + test_valid_deposit_invalid_amount; Tztest.tztest "Test finalization" `Quick test_finalization; Tztest.tztest "Test inbox linked list" `Quick test_inbox_linked_list; + Tztest.tztest "Smoke test commitment" `Quick test_commitments; + Tztest.tztest + "Test commitment predecessor edge cases" + `Quick + test_commitment_predecessor; + Tztest.tztest + "Test case that all commitments are rejected" + `Quick + test_all_commitments_rejected; + Tztest.tztest + "Test commitment retirement" + `Quick + test_commitment_retire_simple; + Tztest.tztest "Test commitment rejection" `Quick test_rejection_propagation; + Tztest.tztest + "Test multiple nonrejected commitment" + `Quick + test_commitment_acceptance; + Tztest.tztest "Test bond finalization" `Quick test_bond_finalization; + Tztest.tztest "Test rejection" `Quick test_rejection; + Tztest.tztest "Test rejection reward" `Quick test_rejection_reward; + Tztest.tztest "Test full inbox" `Quick test_full_inbox; + Tztest.tztest "Test prerejection gc" `Quick test_prerejection_gc; + Tztest.tztest "Test withdraw" `Quick test_withdraw; + Tztest.tztest "Test encoding" `Quick test_encoding; ] diff --git a/src/proto_alpha/lib_protocol/test/pbt/test_script_comparison.ml b/src/proto_alpha/lib_protocol/test/pbt/test_script_comparison.ml index 07631a673b6e673ad90fa6e58d2e4f4bc85b5db8..374d14638a3aac8f5f6853cf5e14899fe18e1780 100644 --- a/src/proto_alpha/lib_protocol/test/pbt/test_script_comparison.ml +++ b/src/proto_alpha/lib_protocol/test/pbt/test_script_comparison.ml @@ -64,6 +64,8 @@ let rec reference_compare_comparable : type a. a comparable_ty -> a -> a -> int | (Timestamp_key _, x, y) -> normalize_compare @@ Script_timestamp.compare x y | (Address_key _, x, y) -> normalize_compare @@ Script_comparable.compare_address x y + | (Tx_rollup_l2_address_key _, x, y) -> + normalize_compare @@ Script_comparable.compare_tx_rollup_l2_address x y | (Bytes_key _, x, y) -> normalize_compare @@ Compare.Bytes.compare x y | (Chain_id_key _, x, y) -> normalize_compare @@ Script_chain_id.compare x y | (Pair_key (tl, tr, _), (lx, rx), (ly, ry)) -> diff --git a/src/proto_alpha/lib_protocol/ticket_balance_key.ml b/src/proto_alpha/lib_protocol/ticket_balance_key.ml index 21123555cf5ca87ff70a9806404f6f40cb3244ef..4d83a70725f7ff7b37a8cb76e080b9631e1296d9 100644 --- a/src/proto_alpha/lib_protocol/ticket_balance_key.ml +++ b/src/proto_alpha/lib_protocol/ticket_balance_key.ml @@ -72,3 +72,17 @@ let ticket_balance_key ctxt ~owner owner_address >>=? fun (owner, ctxt) -> Lwt.return (Ticket_hash.make ctxt ~ticketer ~typ ~contents ~owner) + +let ticket_balance_key_unparsed ctxt ~owner ticketer contents_type contents = + let owner = Destination.Contract owner in + let owner_address = + Script_typed_ir.{destination = owner; entrypoint = Entrypoint.default} + in + Script_ir_translator.unparse_data + ctxt + Script_ir_translator.Optimized_legacy + Script_typed_ir.address_t + owner_address + >>=? fun (owner, ctxt) -> + Lwt.return + (Ticket_hash.make ctxt ~ticketer ~typ:contents_type ~contents ~owner) diff --git a/src/proto_alpha/lib_protocol/ticket_balance_key.mli b/src/proto_alpha/lib_protocol/ticket_balance_key.mli index 1b0900673f4b26486bc15bb51eb659085eb32a59..78ff898bcb4eb413efcd2dee21bbcfaf5e6fa5fe 100644 --- a/src/proto_alpha/lib_protocol/ticket_balance_key.mli +++ b/src/proto_alpha/lib_protocol/ticket_balance_key.mli @@ -28,10 +28,24 @@ global ticket-balance table that tracks ownership of tickets for different tokens. *) +open Alpha_context + (** [ticket_balance_key ctxt ~owner ex_token] returns the [key_hash] of the given [owner] and [ex_token]. *) val ticket_balance_key : - Alpha_context.context -> - owner:Alpha_context.Contract.t -> + context -> + owner:Contract.t -> Ticket_token.ex_token -> - (Alpha_context.Ticket_hash.t * Alpha_context.context) tzresult Lwt.t + (Ticket_hash.t * context) tzresult Lwt.t + +(** [ticket_balance_key_unparsed ctxt ~owner contract ticketer contents_type + contents] returns the [key_hash] of the given [owner] annd ticket. It is + useful in the case where you already have the unparsed ticket and type in + hand. *) +val ticket_balance_key_unparsed : + context -> + owner:Contract.t -> + Script.node -> + Script.node -> + Script.node -> + (Ticket_hash.t * context, error trace) result Lwt.t diff --git a/src/proto_alpha/lib_protocol/ticket_operations_diff.ml b/src/proto_alpha/lib_protocol/ticket_operations_diff.ml index 3bfe258068a9ddd4e47452f2bce1e54757acfd6d..aad60260d1281fa94fd620b70190ad1203844a3d 100644 --- a/src/proto_alpha/lib_protocol/ticket_operations_diff.ml +++ b/src/proto_alpha/lib_protocol/ticket_operations_diff.ml @@ -241,6 +241,9 @@ let tickets_of_operation ctxt destination = Destination.Contract destination; } -> tickets_of_transaction ctxt ~destination ~parameters + | Transaction {destination = Destination.Tx_rollup _; _} -> + (* The ticket accounting is done in the apply function. *) + return (None, ctxt) | Origination {delegate = _; script; credit = _; preorigination} -> tickets_of_origination ctxt ~preorigination script | Delegation _ -> return (None, ctxt) @@ -248,6 +251,10 @@ let tickets_of_operation ctxt | Set_deposits_limit _ -> return (None, ctxt) | Tx_rollup_origination -> return (None, ctxt) | Tx_rollup_submit_batch _ -> return (None, ctxt) + | Tx_rollup_commit _ -> return (None, ctxt) + | Tx_rollup_return_bond _ -> return (None, ctxt) + | Tx_rollup_rejection _ -> return (None, ctxt) + | Tx_rollup_prerejection _ -> return (None, ctxt) | Sc_rollup_originate {kind = _; boot_sector = _} -> return (None, ctxt) | Sc_rollup_add_messages {rollup = _; messages = _} -> return (None, ctxt) diff --git a/src/proto_alpha/lib_protocol/ticket_scanner.ml b/src/proto_alpha/lib_protocol/ticket_scanner.ml index e50eee3be5433519f2eeb86b323218ed79bfcceb..82e6757e04e2e4a5b08a411c77c66692677108be 100644 --- a/src/proto_alpha/lib_protocol/ticket_scanner.ml +++ b/src/proto_alpha/lib_protocol/ticket_scanner.ml @@ -123,6 +123,7 @@ module Ticket_inspection = struct | Timestamp_key _ -> (k [@ocaml.tailcall]) False_ht | Chain_id_key _ -> (k [@ocaml.tailcall]) False_ht | Address_key _ -> (k [@ocaml.tailcall]) False_ht + | Tx_rollup_l2_address_key _ -> (k [@ocaml.tailcall]) False_ht | Pair_key (_, _, _) -> (k [@ocaml.tailcall]) False_ht | Union_key (_, _, _) -> (k [@ocaml.tailcall]) False_ht | Option_key (_, _) -> (k [@ocaml.tailcall]) False_ht @@ -160,6 +161,7 @@ module Ticket_inspection = struct | Key_t _ -> (k [@ocaml.tailcall]) False_ht | Timestamp_t _ -> (k [@ocaml.tailcall]) False_ht | Address_t _ -> (k [@ocaml.tailcall]) False_ht + | Tx_rollup_l2_address_t _ -> (k [@ocaml.tailcall]) False_ht | Bool_t _ -> (k [@ocaml.tailcall]) False_ht | Pair_t (ty1, ty2, _) -> (has_tickets_of_pair [@ocaml.tailcall]) @@ -285,6 +287,7 @@ module Ticket_collection = struct | Timestamp_key _ -> (k [@ocaml.tailcall]) ctxt acc | Chain_id_key _ -> (k [@ocaml.tailcall]) ctxt acc | Address_key _ -> (k [@ocaml.tailcall]) ctxt acc + | Tx_rollup_l2_address_key _ -> (k [@ocaml.tailcall]) ctxt acc | Pair_key (_, _, _) -> (k [@ocaml.tailcall]) ctxt acc | Union_key (_, _, _) -> (k [@ocaml.tailcall]) ctxt acc | Option_key (_, _) -> (k [@ocaml.tailcall]) ctxt acc diff --git a/src/proto_alpha/lib_protocol/token.ml b/src/proto_alpha/lib_protocol/token.ml index 957eff96a6699f29ca039ad8606b8a9430ed6d86..61775f77855ca23d1d8d1d8d2d6bea0cfdff0bf8 100644 --- a/src/proto_alpha/lib_protocol/token.ml +++ b/src/proto_alpha/lib_protocol/token.ml @@ -44,6 +44,7 @@ type source = | `Baking_bonuses | `Minted | `Liquidity_baking_subsidies + | `Rollup_bond_return | container ] type sink = @@ -51,6 +52,7 @@ type sink = | `Double_signing_punishments | `Lost_endorsing_rewards of Signature.Public_key_hash.t * bool * bool | `Burned + | `Rollup_bond | container ] let allocated ctxt stored = @@ -111,6 +113,7 @@ let credit ctxt dest amount origin = | `Lost_endorsing_rewards (d, p, r) -> return (ctxt, Lost_endorsing_rewards (d, p, r)) | `Burned -> return (ctxt, Burned) + | `Rollup_bond -> return (ctxt, Rollup_bond) | `Contract dest -> Contract_storage.credit_only_call_from_token ctxt dest amount >|=? fun ctxt -> (ctxt, Contract dest) @@ -171,6 +174,7 @@ let spend ctxt src amount origin = | `Invoice -> return (ctxt, Invoice) | `Initial_commitments -> return (ctxt, Initial_commitments) | `Minted -> return (ctxt, Minted) + | `Rollup_bond_return -> return (ctxt, Rollup_bond) | `Liquidity_baking_subsidies -> return (ctxt, Liquidity_baking_subsidies) | `Revelation_rewards -> return (ctxt, Nonce_revelation_rewards) | `Double_signing_evidence_rewards -> diff --git a/src/proto_alpha/lib_protocol/token.mli b/src/proto_alpha/lib_protocol/token.mli index ef8c0eabcdcad1a573e8bbc9d50a01bea52f7a23..a5ccab80f22dcf1c8fbc6e20b7df43c8348c000a 100644 --- a/src/proto_alpha/lib_protocol/token.mli +++ b/src/proto_alpha/lib_protocol/token.mli @@ -64,6 +64,7 @@ type source = | `Baking_bonuses | `Minted | `Liquidity_baking_subsidies + | `Rollup_bond_return | container ] (** [sink] is the type of token receivers. Token receivers that are not @@ -73,6 +74,7 @@ type sink = | `Double_signing_punishments | `Lost_endorsing_rewards of Signature.Public_key_hash.t * bool * bool | `Burned + | `Rollup_bond | container ] (** [allocated ctxt container] returns true if [balance ctxt container] is diff --git a/src/proto_alpha/lib_protocol/tx_rollup_commitments_repr.ml b/src/proto_alpha/lib_protocol/tx_rollup_commitments_repr.ml new file mode 100644 index 0000000000000000000000000000000000000000..80f11248e995de50aeb74718defd0964c84ae307 --- /dev/null +++ b/src/proto_alpha/lib_protocol/tx_rollup_commitments_repr.ml @@ -0,0 +1,407 @@ +(*****************************************************************************) +(* *) +(* Open Source License *) +(* Copyright (c) 2022 Marigold *) +(* Copyright (c) 2022 Nomadic Labs *) +(* Copyright (c) 2022 Oxhead Alpha *) +(* *) +(* Permission is hereby granted, free of charge, to any person obtaining a *) +(* copy of this software and associated documentation files (the "Software"),*) +(* to deal in the Software without restriction, including without limitation *) +(* the rights to use, copy, modify, merge, publish, distribute, sublicense, *) +(* and/or sell copies of the Software, and to permit persons to whom the *) +(* Software is furnished to do so, subject to the following conditions: *) +(* *) +(* The above copyright notice and this permission notice shall be included *) +(* in all copies or substantial portions of the Software. *) +(* *) +(* THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR*) +(* IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, *) +(* FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL *) +(* THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER*) +(* LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING *) +(* FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER *) +(* DEALINGS IN THE SOFTWARE. *) +(* *) +(*****************************************************************************) + +type error += (* `Branch *) Commitment_hash_already_submitted + +type error += (* `Branch *) Two_commitments_from_one_committer + +type error += (* `Branch *) Wrong_commitment_predecessor_level + +type error += (* `Temporary *) Missing_commitment_predecessor + +type error += (* `Temporary *) Wrong_batch_count + +type error += (* `Temporary *) Retire_uncommitted_level + +type error += (* `Temporary *) No_such_commitment + +type error += (* `Temporary *) + Bond_does_not_exist of Contract_repr.t + +type error += (* `Temporary *) Bond_in_use of Contract_repr.t + +type error += (* `Temporary *) Too_many_unfinalized_levels + +type error += (* `Permanent *) No_such_batch of Raw_level_repr.t * int + +let () = + let open Data_encoding in + (* Commitment_hash_already_submitted *) + register_error_kind + `Temporary + ~id:"Commitment_hash_already_submitted" + ~title:"Someone already made this commitment" + ~description:"The requested commitment is a duplicate" + unit + (function Commitment_hash_already_submitted -> Some () | _ -> None) + (fun () -> Commitment_hash_already_submitted) ; + (* Two_commitments_from_one_committer *) + register_error_kind + `Temporary + ~id:"Two_commitments_from_one_committer" + ~title:"This contract already made a different commitment at this level" + ~description: + "This contract already made a different commitment at this level" + unit + (function Two_commitments_from_one_committer -> Some () | _ -> None) + (fun () -> Two_commitments_from_one_committer) ; + (* Wrong_commitment_predecessor_level *) + register_error_kind + `Temporary + ~id:"Wrong_commitment_predecessor_level" + ~title:"This commitment's predecessor is invalid" + ~description: + "This commitment has predecessor but shouldn't, or doesn't but should" + unit + (function Wrong_commitment_predecessor_level -> Some () | _ -> None) + (fun () -> Wrong_commitment_predecessor_level) ; + (* Missing_commitment_predecessor *) + register_error_kind + `Temporary + ~id:"Missing_commitment_predecessor" + ~title:"This commitment refers to a predecessor that doesn't exist" + ~description:"This commitment refers to a predecessor that doesn't exist" + unit + (function Missing_commitment_predecessor -> Some () | _ -> None) + (fun () -> Missing_commitment_predecessor) ; + (* Wrong_batch_count *) + register_error_kind + `Temporary + ~id:"Wrong_batch_count" + ~title:"This commitment has the wrong number of batches" + ~description: + "This commitment has a different number of batches than its inbox" + unit + (function Wrong_batch_count -> Some () | _ -> None) + (fun () -> Wrong_batch_count) ; + (* Retire_uncommitted_level *) + register_error_kind + `Permanent + ~id:"Retire_uncommitted_level" + ~title:"Tried to retire a rollup level with no commitments" + ~description: + "An attempt was made to retire a rollup level with no commitments" + empty + (function Retire_uncommitted_level -> Some () | _ -> None) + (fun () -> Retire_uncommitted_level) ; + (* No_such_commitment *) + register_error_kind + `Permanent + ~id:"No_such_commitment" + ~title:"Tried to reject a commitment that doesn't exist" + ~description:"An attempt was made to reject a nonexistent commitment" + empty + (function No_such_commitment -> Some () | _ -> None) + (fun () -> No_such_commitment) ; + (* Bond_does_not_exist *) + register_error_kind + `Temporary + ~id:"Bond_does_not_exist" + ~title:"This account does not have a bond for this rollup" + ~description:"This account does not have a bond for this rollup" + (obj1 (req "contract" Contract_repr.encoding)) + (function Bond_does_not_exist contract -> Some contract | _ -> None) + (fun contract -> Bond_does_not_exist contract) ; + (* Bond_in_use *) + register_error_kind + `Temporary + ~id:"Bond_in_use" + ~title:"This account's bond is in use for one or more commitments" + ~description:"This account's bond is in use for one or more commitments" + (obj1 (req "contract" Contract_repr.encoding)) + (function Bond_in_use contract -> Some contract | _ -> None) + (fun contract -> Bond_in_use contract) ; + (* Too_many_unfinalized_levels *) + register_error_kind + `Temporary + ~id:"Too_many_unfinalized_levels" + ~title:"This rollup hasn't had a commitment in too long" + ~description: + "This rollup hasn't a commitment in too long. We don't allow new \ + messages to keep commitment gas reasonable." + empty + (function Too_many_unfinalized_levels -> Some () | _ -> None) + (fun () -> Too_many_unfinalized_levels) ; + (* No_such_batch *) + register_error_kind + `Temporary + ~id:"No_such_batch" + ~title:"This rejection wrongly attempts to reject a non-existent batch" + ~description: + "This rejection wrongly attempts to reject a non-existent batch" + (obj2 + (req "level" Raw_level_repr.encoding) + (req "index" Data_encoding.int31)) + (function No_such_batch (level, index) -> Some (level, index) | _ -> None) + (fun (level, index) -> No_such_batch (level, index)) + +let compare_or cmp c1 c2 f = match cmp c1 c2 with 0 -> f () | diff -> diff + +module Commitment_hash = struct + let commitment_hash = "\017\249\195\013" (* toc1(54) *) + + module H = + Blake2B.Make + (Base58) + (struct + let name = "Commitment_hash" + + let title = "A commitment ID" + + let b58check_prefix = commitment_hash + + let size = Some 32 + end) + + include H + + let () = Base58.check_encoded_prefix b58check_encoding "toc1" 54 + + include Path_encoding.Make_hex (H) + + let rpc_arg = + let construct = Data_encoding.Binary.to_string_exn encoding in + let destruct str = + Option.value_e ~error:"Failed to decode commitment" + @@ Data_encoding.Binary.of_string_opt encoding str + in + RPC_arg.make + ~descr:"A tx_rollup commitment." + ~name:"tx_rollup_commitment" + ~construct + ~destruct + () +end + +module Commitment = struct + type withdrawal = { + contract : Contract_repr.t; + ticket : Ticket_hash_repr.t; + amount : int64; + } + + let withdrawal_encoding = + Data_encoding.( + conv + (fun {contract; ticket; amount} -> (contract, ticket, amount)) + (fun (contract, ticket, amount) -> {contract; ticket; amount}) + (obj3 + (req "contract" Contract_repr.encoding) + (req "ticket" Ticket_hash_repr.encoding) + (req "amount" int64))) + + let pp_withdrawal : Format.formatter -> withdrawal -> unit = + fun fmt {contract; ticket; amount} -> + Format.fprintf + fmt + "withdrawal to %a of %Ld of %a" + Contract_repr.pp + contract + amount + Ticket_hash_repr.pp + ticket + + let compare_withdrawal a b = + compare_or Contract_repr.compare a.contract b.contract (fun () -> + compare_or Ticket_hash_repr.compare a.ticket b.ticket (fun () -> + Int64.compare a.amount b.amount)) + + type batch_commitment = { + effects : withdrawal list; + (* TODO: replace bytes with Irmin: + https://gitlab.com/tezos/tezos/-/issues/2444 + *) + root : bytes; + } + + module Batch = struct + type t = batch_commitment + + let encoding = + Data_encoding.( + conv + (fun {effects; root} -> (effects, root)) + (fun (effects, root) -> {effects; root}) + (obj2 (req "effects" (list withdrawal_encoding)) (req "root" bytes))) + + let pp : Format.formatter -> t -> unit = + fun fmt {effects; root} -> + Format.fprintf + fmt + "{effects = %a; root= %a}" + (Format.pp_print_list pp_withdrawal) + effects + Hex.pp + (Hex.of_bytes root) + + include Compare.Make (struct + type nonrec t = t + + let compare {effects = effects1; root = root1} + {effects = effects2; root = root2} = + compare_or Bytes.compare root1 root2 (fun () -> + List.compare compare_withdrawal effects1 effects2) + end) + end + + let batch_commitment_equal : batch_commitment -> batch_commitment -> bool = + Batch.equal + + type t = { + level : Raw_level_repr.t; + batches : batch_commitment list; + predecessor : Commitment_hash.t option; + } + + include Compare.Make (struct + type nonrec t = t + + module Compare_root_list = Compare.List (Batch) + + let compare r1 r2 = + compare_or Raw_level_repr.compare r1.level r2.level (fun () -> + compare_or Compare_root_list.compare r1.batches r2.batches (fun () -> + Option.compare + Commitment_hash.compare + r1.predecessor + r2.predecessor)) + end) + + let pp : Format.formatter -> t -> unit = + fun fmt t -> + Format.fprintf + fmt + "commitment %a : batches = %a predecessor %a" + Raw_level_repr.pp + t.level + (Format.pp_print_list Batch.pp) + t.batches + (Format.pp_print_option Commitment_hash.pp) + t.predecessor + + let encoding = + let open Data_encoding in + conv + (fun {level; batches; predecessor} -> (level, batches, predecessor)) + (fun (level, batches, predecessor) -> {level; batches; predecessor}) + (obj3 + (req "level" Raw_level_repr.encoding) + (req "batches" (list Batch.encoding)) + (req "predecessor" (option Commitment_hash.encoding))) + + let hash t = + let to_bytes_exn = Data_encoding.Binary.to_bytes_exn in + let level_bytes = to_bytes_exn Raw_level_repr.encoding t.level in + let predecessor_bytes = + Option.fold + ~none:Bytes.empty + ~some:(fun pred -> Commitment_hash.to_bytes pred) + t.predecessor + in + let batches_bytes = + to_bytes_exn (Data_encoding.list Batch.encoding) t.batches + in + Commitment_hash.hash_bytes [level_bytes; predecessor_bytes; batches_bytes] + + module Index = struct + type t = Commitment_hash.t + + let path_length = 1 + + let to_path c l = + let raw_key = + Data_encoding.Binary.to_bytes_exn Commitment_hash.encoding c + in + let (`Hex key) = Hex.of_bytes raw_key in + key :: l + + let of_path = function + | [key] -> + Option.bind + (Hex.to_bytes (`Hex key)) + (Data_encoding.Binary.of_bytes_opt Commitment_hash.encoding) + | _ -> None + + let rpc_arg = Commitment_hash.rpc_arg + + let encoding = Commitment_hash.encoding + + let compare = Commitment_hash.compare + end +end + +type pending_commitment = { + commitment : Commitment.t; + hash : Commitment_hash.t; + committer : Contract_repr.t; + submitted_at : Raw_level_repr.t; +} + +let pp_pending_commitment : Format.formatter -> pending_commitment -> unit = + fun fmt {commitment; hash; committer; submitted_at} -> + Format.fprintf + fmt + "pending_commitment %a; hash = %a; committer = %a; submitted_at = %a" + Commitment.pp + commitment + Commitment_hash.pp + hash + Contract_repr.pp_short + committer + Raw_level_repr.pp + submitted_at + +let pending_commitment_encoding = + Data_encoding.( + conv + (fun {commitment; committer; submitted_at; _} -> + (commitment, committer, submitted_at)) + (fun (commitment, committer, submitted_at) -> + let hash = Commitment.hash commitment in + {hash; commitment; committer; submitted_at}) + (obj3 + (req "commitment" Commitment.encoding) + (req "commiter" Contract_repr.encoding) + (req "submitted_at" Raw_level_repr.encoding))) + +type t = pending_commitment list + +let encoding = Data_encoding.(list pending_commitment_encoding) + +let empty = [] + +let append : t -> Contract_repr.t -> Commitment.t -> Raw_level_repr.t -> t = + fun t contract commitment level -> + let hash = Commitment.hash commitment in + {hash; commitment; committer = contract; submitted_at = level} :: t + +let commitment_exists : t -> Commitment_hash.t -> bool = + fun t hash -> List.exists (fun {hash = h; _} -> Commitment_hash.(h = hash)) t + +let commitment_with_committer_exists : t -> Contract_repr.t -> bool = + fun t contract -> + List.exists (fun {committer; _} -> Contract_repr.(committer = contract)) t diff --git a/src/proto_alpha/lib_protocol/tx_rollup_commitments_repr.mli b/src/proto_alpha/lib_protocol/tx_rollup_commitments_repr.mli new file mode 100644 index 0000000000000000000000000000000000000000..5b20fb403d318ad121427969a3f83f3df412a741 --- /dev/null +++ b/src/proto_alpha/lib_protocol/tx_rollup_commitments_repr.mli @@ -0,0 +1,124 @@ +(*****************************************************************************) +(* *) +(* Open Source License *) +(* Copyright (c) 2022 Marigold *) +(* Copyright (c) 2022 Nomadic Labs *) +(* Copyright (c) 2022 Oxhead Alpha *) +(* *) +(* Permission is hereby granted, free of charge, to any person obtaining a *) +(* copy of this software and associated documentation files (the "Software"),*) +(* to deal in the Software without restriction, including without limitation *) +(* the rights to use, copy, modify, merge, publish, distribute, sublicense, *) +(* and/or sell copies of the Software, and to permit persons to whom the *) +(* Software is furnished to do so, subject to the following conditions: *) +(* *) +(* The above copyright notice and this permission notice shall be included *) +(* in all copies or substantial portions of the Software. *) +(* *) +(* THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR*) +(* IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, *) +(* FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL *) +(* THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER*) +(* LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING *) +(* FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER *) +(* DEALINGS IN THE SOFTWARE. *) +(* *) +(*****************************************************************************) + +type error += (* `Branch *) Commitment_hash_already_submitted + +type error += (* `Branch *) Two_commitments_from_one_committer + +type error += (* `Branch *) Wrong_commitment_predecessor_level + +type error += (* `Temporary *) Missing_commitment_predecessor + +type error += (* `Branch *) Wrong_batch_count + +type error += (* `Branch *) + Retire_uncommitted_level + +type error += (* `Temporary *) No_such_commitment + +type error += (* `Temporary *) + Bond_does_not_exist of Contract_repr.t + +type error += (* `Temporary *) Bond_in_use of Contract_repr.t + +type error += (* `Temporary *) Too_many_unfinalized_levels + +type error += (* `Permanent *) No_such_batch of Raw_level_repr.t * int + +(** A specialized Blake2B implementation for hashing commitments with + "toc1" as a base58 prefix *) +module Commitment_hash : sig + val commitment_hash : string + + include S.HASH +end + +module Commitment : sig + type withdrawal = { + contract : Contract_repr.t; + ticket : Ticket_hash_repr.t; + amount : int64; + } + + type batch_commitment = {effects : withdrawal list; root : bytes} + + val batch_commitment_equal : batch_commitment -> batch_commitment -> bool + + (* A commitment describes the inbox of a particular [level]. It includes + one Merkle tree root for each of the [batches]. It has a [predecessor], + which is used to get the Merkle root before any inboxes are processed. + If [predecessor] is None, the commitment is for the first inbox with + messages in this rollup, and the initial Merkle root is the empty + tree. *) + type t = { + level : Raw_level_repr.t; + batches : batch_commitment list; + predecessor : Commitment_hash.t option; + } + + val ( = ) : t -> t -> bool + + val pp : Format.formatter -> t -> unit + + val encoding : t Data_encoding.t + + val hash : t -> Commitment_hash.t + + module Index : Storage_description.INDEX with type t = Commitment_hash.t +end + +(** A [pending_commitment] is a commitment which has not yet become final. + The [hash] is redundant and is only stored to reduce computation. We + track the level that the commitment was submitted at; 30 blocks later, + it will become final if not rejected. *) +type pending_commitment = { + commitment : Commitment.t; + hash : Commitment_hash.t; + committer : Contract_repr.t; + submitted_at : Raw_level_repr.t; +} + +val pp_pending_commitment : Format.formatter -> pending_commitment -> unit + +(** This is the type that we store, ordered in reverse priority order. *) +type t = pending_commitment list + +val encoding : t Data_encoding.t + +val empty : t + +(** [append commitments contract commitment level] appends a new commitment + to a list of commitments. *) +val append : t -> Contract_repr.t -> Commitment.t -> Raw_level_repr.t -> t + +(** [commitment_exists commitments t hash] returns true if a commitment + with this [hash] already exists in this list. *) +val commitment_exists : t -> Commitment_hash.t -> bool + +(** [commitment_with_committer_exists commitments t contract] returns + true if a commitment by this [contract] already exists in this list. *) +val commitment_with_committer_exists : t -> Contract_repr.t -> bool diff --git a/src/proto_alpha/lib_protocol/tx_rollup_commitments_storage.ml b/src/proto_alpha/lib_protocol/tx_rollup_commitments_storage.ml new file mode 100644 index 0000000000000000000000000000000000000000..52149d132a23c8573d3bdb813dd86964b74a353f --- /dev/null +++ b/src/proto_alpha/lib_protocol/tx_rollup_commitments_storage.ml @@ -0,0 +1,645 @@ +(*****************************************************************************) +(* *) +(* Open Source License *) +(* Copyright (c) 2021 Marigold *) +(* Copyright (c) 2021 Nomadic Labs *) +(* Copyright (c) 2021 Oxhead Alpha *) +(* *) +(* Permission is hereby granted, free of charge, to any person obtaining a *) +(* copy of this software and associated documentation files (the "Software"),*) +(* to deal in the Software without restriction, including without limitation *) +(* the rights to use, copy, modify, merge, publish, distribute, sublicense, *) +(* and/or sell copies of the Software, and to permit persons to whom the *) +(* Software is furnished to do so, subject to the following conditions: *) +(* *) +(* The above copyright notice and this permission notice shall be included *) +(* in all copies or substantial portions of the Software. *) +(* *) +(* THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR*) +(* IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, *) +(* FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL *) +(* THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER*) +(* LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING *) +(* FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER *) +(* DEALINGS IN THE SOFTWARE. *) +(* *) +(*****************************************************************************) + +let just_ctxt (ctxt, _, _) = ctxt + +open Tx_rollup_commitments_repr + +let get_or_empty_commitments : + Raw_context.t -> + Raw_level_repr.t * Tx_rollup_repr.t -> + (Raw_context.t * Tx_rollup_commitments_repr.t) tzresult Lwt.t = + fun ctxt key -> + Storage.Tx_rollup.Commitment_list.find ctxt key >|=? fun (ctxt, commitment) -> + Option.fold + commitment + ~none:(ctxt, Tx_rollup_commitments_repr.empty) + ~some:(fun l -> (ctxt, l)) + +let get_next_level ctxt tx_rollup level = + Tx_rollup_inbox_storage.get_adjacent_levels ctxt level tx_rollup + >|=? fun (ctxt, _, next_level) -> (ctxt, next_level) + +let get_prev_level ctxt tx_rollup level = + Tx_rollup_inbox_storage.get_adjacent_levels ctxt level tx_rollup + >|=? fun (ctxt, predecessor_level, _) -> (ctxt, predecessor_level) + +let increment_commitment_bond ctxt tx_rollup contract bond_tez = + let bond_key = (tx_rollup, contract) in + ( Storage.Tx_rollup.Commitment_bond.find ctxt bond_key >>=? fun (ctxt, bond) -> + match bond with + | Some (count, tez) -> return (ctxt, (count + 1, tez)) + | None -> + ( Storage.Tx_rollup.Commitment_bond.remove ctxt bond_key + >>=? fun (ctxt, _, _) -> + Storage.Tx_rollup.Frozen_commitments.find ctxt contract >>=? function + | None -> return bond_tez + | Some old -> Lwt.return @@ Tez_repr.(old +? bond_tez) ) + >>=? fun new_tez -> + Storage.Tx_rollup.Frozen_commitments.add ctxt contract new_tez + >>= fun ctxt -> return (ctxt, (1, bond_tez)) ) + >>=? fun (ctxt, new_bond) -> + Storage.Tx_rollup.Commitment_bond.add ctxt bond_key new_bond >|=? just_ctxt + +let reduce_commitment_bond ctxt tx_rollup contract = + let bond_key = (tx_rollup, contract) in + ( Storage.Tx_rollup.Commitment_bond.find ctxt bond_key >>=? fun (ctxt, bond) -> + match bond with + | Some (count, tez) -> return (ctxt, (count - 1, tez)) + | None -> assert false ) + >>=? fun (ctxt, (count, tez)) -> + let new_bond = (count, tez) in + Storage.Tx_rollup.Commitment_bond.add ctxt bond_key new_bond >|=? just_ctxt + +let remove_bond : + Raw_context.t -> + Tx_rollup_repr.t -> + Contract_repr.t -> + Raw_context.t tzresult Lwt.t = + fun ctxt tx_rollup contract -> + let bond_key = (tx_rollup, contract) in + Storage.Tx_rollup.Commitment_bond.find ctxt bond_key >>=? fun (ctxt, bond) -> + match bond with + | None -> fail (Tx_rollup_commitments_repr.Bond_does_not_exist contract) + | Some (0, tez) -> + Storage.Tx_rollup.Commitment_bond.remove ctxt bond_key + >>=? fun (ctxt, _, _) -> + Storage.Tx_rollup.Frozen_commitments.get ctxt contract >>=? fun old -> + Tez_repr.(old -? tez) >>?= fun new_tez -> + Storage.Tx_rollup.Frozen_commitments.add ctxt contract new_tez >>= return + | Some _ -> fail (Tx_rollup_commitments_repr.Bond_in_use contract) + +let check_commitment_predecessor_hash ctxt tx_rollup (commitment : Commitment.t) + = + let level = commitment.level in + (* Check that level has the correct predecessor *) + get_prev_level ctxt tx_rollup level >>=? fun (ctxt, predecessor_level) -> + match (predecessor_level, commitment.predecessor) with + | (None, None) -> return ctxt + | (Some _, None) | (None, Some _) -> fail Wrong_commitment_predecessor_level + | (Some predecessor_level, Some hash) -> + (* The predecessor level must include this commitment*) + get_or_empty_commitments ctxt (predecessor_level, tx_rollup) + >>=? fun (ctxt, predecesor_commitments) -> + fail_unless + (Tx_rollup_commitments_repr.commitment_exists + predecesor_commitments + hash) + Missing_commitment_predecessor + >>=? fun () -> return ctxt + +let add_commitment ctxt tx_rollup contract (commitment : Commitment.t) tez = + let key = (commitment.level, tx_rollup) in + get_or_empty_commitments ctxt key >>=? fun (ctxt, pending) -> + let hash = Commitment.hash commitment in + (* We fail if this contract already has a commitment at this level, + or if anyone has already made this commitment at this level; a + bond entitles you to at most one commitment per level. *) + fail_when (commitment_exists pending hash) Commitment_hash_already_submitted + >>=? fun () -> + fail_when + (commitment_with_committer_exists pending contract) + Two_commitments_from_one_committer + >>=? fun () -> + Tx_rollup_inbox_storage.get ctxt ~level:(`Level commitment.level) tx_rollup + >>=? fun (ctxt, inbox) -> + let expected_len = List.length inbox.contents in + let actual_len = List.length commitment.batches in + fail_unless Compare.Int.(expected_len = actual_len) Wrong_batch_count + >>=? fun () -> + check_commitment_predecessor_hash ctxt tx_rollup commitment >>=? fun ctxt -> + let current_level = (Raw_context.current_level ctxt).level in + let new_pending = + Tx_rollup_commitments_repr.append pending contract commitment current_level + in + Storage.Tx_rollup.Commitment_list.add ctxt key new_pending + >>=? fun (ctxt, _, _) -> increment_commitment_bond ctxt tx_rollup contract tez + +module Contract_set = Set.Make (Contract_repr) +module Commitment_set = Set.Make (Commitment_hash) + +let rec accumulate_bad_commitments : + Raw_context.t -> + Tx_rollup_repr.t -> + Raw_level_repr.t -> + Raw_level_repr.t -> + Commitment_set.t -> + Contract_set.t -> + (Commitment_set.t * Contract_set.t) tzresult Lwt.t = + fun ctxt tx_rollup level top commitments contracts -> + let add_bad_commitments (commitments, contracts) + {commitment; hash; committer; _} = + if + Option.value ~default:false + @@ Option.map + (fun predecessor -> Commitment_set.mem predecessor commitments) + commitment.predecessor + || Contract_set.mem committer contracts + then + (Commitment_set.add hash commitments, Contract_set.add committer contracts) + else (commitments, contracts) + in + if Raw_level_repr.(level > top) then return (commitments, contracts) + else + let key = (level, tx_rollup) in + Storage.Tx_rollup.Commitment_list.find ctxt key + >>=? fun (ctxt, commitment_list) -> + let pending = + match commitment_list with None -> [] | Some pending -> pending + in + let (commitments, contracts) = + List.fold_left add_bad_commitments (commitments, contracts) pending + in + get_next_level ctxt tx_rollup level >>=? fun (ctxt, next_level) -> + match next_level with + | None -> return (commitments, contracts) + | Some next_level -> + accumulate_bad_commitments + ctxt + tx_rollup + next_level + top + commitments + contracts + +let rec remove_successors : + Raw_context.t -> + Tx_rollup_repr.t -> + Raw_level_repr.t -> + Raw_level_repr.t -> + Commitment_set.t -> + Raw_context.t tzresult Lwt.t = + fun ctxt tx_rollup level top commitments -> + if Raw_level_repr.(level > top) then return ctxt + else + let key = (level, tx_rollup) in + get_next_level ctxt tx_rollup level >>=? fun (ctxt, next_level) -> + Storage.Tx_rollup.Commitment_list.find ctxt key + >>=? fun (ctxt, commitment_list) -> + match commitment_list with + | None -> ( + match next_level with + | None -> return ctxt + | Some next_level -> + remove_successors ctxt tx_rollup next_level top commitments) + | Some pending -> + let next_commitments = + List.fold_left + (fun next_commitments {commitment; hash; _} -> + if + Option.value ~default:false + @@ Option.map + (fun predecessor -> + Commitment_set.mem predecessor commitments) + commitment.predecessor + then Commitment_set.add hash next_commitments + else next_commitments) + commitments + pending + in + if not @@ Commitment_set.is_empty commitments then + let (to_remove, new_pending) = + List.partition + (fun {hash; _} -> Commitment_set.mem hash next_commitments) + pending + in + List.fold_left_es + (fun ctxt {committer; _} -> + reduce_commitment_bond ctxt tx_rollup committer) + ctxt + to_remove + >>=? fun ctxt -> + Storage.Tx_rollup.Commitment_list.add ctxt key new_pending + >>=? fun (ctxt, _, _) -> + match next_level with + | None -> return ctxt + | Some next_level -> + remove_successors ctxt tx_rollup next_level top next_commitments + else return ctxt + +let rec remove_commitments_by_hash : + Raw_context.t -> + Tx_rollup_repr.t -> + Raw_level_repr.t -> + Raw_level_repr.t -> + Commitment_set.t -> + Raw_context.t tzresult Lwt.t = + fun ctxt tx_rollup level top commitments -> + if Raw_level_repr.(level > top) then return ctxt + else + let key = (level, tx_rollup) in + Storage.Tx_rollup.Commitment_list.find ctxt key + >>=? fun (ctxt, commitment_list) -> + (match commitment_list with + | None -> + (* No commitments at this level -- just recurse *) + return ctxt + | Some pending -> + let new_pending = + List.filter + (fun {hash; _} -> not @@ Commitment_set.mem hash commitments) + pending + in + Storage.Tx_rollup.Commitment_list.add ctxt key new_pending + >|=? just_ctxt) + >>=? fun ctxt -> + get_next_level ctxt tx_rollup level >>=? fun (ctxt, next_level) -> + match next_level with + | None -> return ctxt + | Some next_level -> + remove_commitments_by_hash ctxt tx_rollup next_level top commitments + +let adjust_successful_prerejection ctxt tx_rollup level hash contract counter = + Storage.Tx_rollup.Successful_prerejections.find + ((ctxt, level), tx_rollup) + hash + >>=? fun (ctxt, existing) -> + match existing with + | None -> + Storage.Tx_rollup.Successful_prerejections.add + ((ctxt, level), tx_rollup) + hash + (counter, contract) + >|=? just_ctxt + | Some (old_counter, _) when Compare.Z.(old_counter > counter) -> + Storage.Tx_rollup.Successful_prerejections.add + ((ctxt, level), tx_rollup) + hash + (counter, contract) + >|=? just_ctxt + | Some _ -> return ctxt + +let reject_commitment ctxt tx_rollup (level : Raw_level_repr.t) + (commitment_id : Commitment_hash.t) (contract : Contract_repr.t) + (counter : Z.t) = + let top = (Raw_context.current_level ctxt).level in + Storage.Tx_rollup.Commitment_list.get ctxt (level, tx_rollup) + >>=? fun (ctxt, commitments) -> + let matching_commitments = + List.filter + (fun {hash; _} -> Commitment_hash.(hash = commitment_id)) + commitments + in + match List.hd matching_commitments with + | None -> + (* This commit has already been rejected, but maybe this rejection + corresponds to an earlier prerejection which needs to be credited. *) + adjust_successful_prerejection + ctxt + tx_rollup + level + commitment_id + contract + counter + | Some to_remove -> + let initial_bad_commitments = Commitment_set.of_list [commitment_id] in + let initial_evildoers = Contract_set.of_list [to_remove.committer] in + let rec aux bad_commitments evildoers = + accumulate_bad_commitments + ctxt + tx_rollup + level + top + bad_commitments + evildoers + >>=? fun (new_bad_commitments, new_evildoers) -> + if + Compare.Int.( + Contract_set.cardinal new_evildoers + = Contract_set.cardinal evildoers + && Commitment_set.cardinal new_bad_commitments + = Commitment_set.cardinal bad_commitments) + then return (new_bad_commitments, new_evildoers) + else aux new_bad_commitments new_evildoers + in + aux initial_bad_commitments initial_evildoers + >>=? fun (bad_commitments, evildoers) -> + remove_commitments_by_hash ctxt tx_rollup level top bad_commitments + >>=? fun ctxt -> + Contract_set.fold_es + (fun contract ctxt -> + let key = (tx_rollup, contract) in + Storage.Tx_rollup.Commitment_bond.remove ctxt key >|=? just_ctxt) + evildoers + ctxt + >>=? fun ctxt -> + adjust_successful_prerejection + ctxt + tx_rollup + level + commitment_id + contract + counter + +let find_commitment_by_hash ctxt tx_rollup level hash = + Storage.Tx_rollup.Commitment_list.get ctxt (level, tx_rollup) + >|=? fun (ctxt, commitments) -> + let pending_commitment = + List.find + (fun {commitment; _} -> + Commitment_hash.(hash = Commitment.hash commitment)) + commitments + in + (ctxt, pending_commitment) + +let get_commitment_roots ctxt tx_rollup (level : Raw_level_repr.t) + (commitment_id : Commitment_hash.t) (index : int) = + let find_commitment_or_die ctxt level commitment_id = + find_commitment_by_hash ctxt tx_rollup level commitment_id + >>=? fun (ctxt, maybe_pending) -> + Option.map_es (fun pending -> return (ctxt, pending)) maybe_pending + >>=? fun maybe_pending -> + Lwt.return + @@ Option.value_e + ~error:(Error_monad.trace_of_error No_such_commitment) + maybe_pending + in + find_commitment_or_die ctxt level commitment_id + >>=? fun (ctxt, pending_commitment) -> + let commitment = pending_commitment.commitment in + let nth_root (commitment : Commitment.t) n = + let nth = List.nth commitment.batches n in + Option.value_e + ~error:(Error_monad.trace_of_error (No_such_batch (level, index))) + nth + in + (match index with + | 0 -> ( + match commitment.predecessor with + | None -> + (* TODO: empty merkle tree when we have this*) + let empty : Tx_rollup_commitments_repr.Commitment.batch_commitment = + {effects = []; root = Bytes.empty} + in + return (ctxt, empty) + | Some prev_hash -> + get_prev_level ctxt tx_rollup level >>=? fun (ctxt, prev_level) -> + let prev_level = + match prev_level with + | None -> assert false + | Some prev_level -> prev_level + in + find_commitment_or_die ctxt prev_level prev_hash + >>=? fun (ctxt, {commitment = {batches; _}; _}) -> + (let last = List.last_opt batches in + Option.value_e + ~error:(Error_monad.trace_of_error (No_such_batch (level, -1))) + last) + >>?= fun p -> return (ctxt, p)) + | index -> nth_root commitment (index - 1) >>?= fun p -> return (ctxt, p)) + >>=? fun (ctxt, before_hash) -> + nth_root commitment index >>?= fun after_hash -> + return (ctxt, (before_hash, after_hash)) + +(** [gc_prerejections ctxt level] Removes a few old prerejections, if + any are older than [level]. We want to bound computation, and we + know we'll get another chance later to remove more, so we don't + necessarily remove them all. *) +let gc_prerejections ctxt level = + let rec aux ctxt index count = + if Compare.Int.(count = 0) then return (ctxt, index) + else + Storage.Tx_rollup.Prerejection_by_index.find ctxt index + >>=? fun (ctxt, candidate) -> + match candidate with + | None -> + (* We have advanced past the last prerejection. This technically + means that Oldest_prerejection will point to a nonexistent + index, but that is OK -- it'll become correct again as soon + someone creates a new one, and in the meantime it does no + harm. *) + return (ctxt, index) + | Some (rejection, candidate_level) -> + if Raw_level_repr.(candidate_level > level) then + (* This and every subsequent prerejection are too new. *) + return (ctxt, index) + else + Storage.Tx_rollup.Prerejection_by_index.remove ctxt index + >>=? fun (ctxt, _, _) -> + Storage.Tx_rollup.Prerejection.remove ctxt rejection + >>=? fun (ctxt, _, _) -> aux ctxt (Z.succ index) (count - 1) + in + Storage.Tx_rollup.Oldest_prerejection.find ctxt >>=? function + | None -> return ctxt + | Some oldest -> + (* This number is pretty arbitrary -- it's a balance between + how quickly a storm of prerejections gets removed vs the max + gas cost of any one prerejection. Ten is an easy number to + reason about: if someone (somehow) creates a million + prerejections, then 100k new prerejections will clean + them up, and 10k newer prerejections will clean up the 100k, + and so forth, leading to a total cleanup (except for the last + straggler) in 6 steps. *) + aux ctxt oldest 10 >>=? fun (ctxt, new_oldest) -> + Storage.Tx_rollup.Oldest_prerejection.add ctxt new_oldest >|= ok + +let get_oldest_prerejection ctxt = + Storage.Tx_rollup.Oldest_prerejection.find ctxt + +let apply_effects ctxt tx_rollup (commitment : Commitment.t) = + List.fold_left_es + (fun ctxt Commitment.{effects; _} -> + List.fold_left_es + (fun ctxt ({contract; ticket; amount} : Commitment.withdrawal) -> + ( Storage.Tx_rollup.Ticket_offramp.find + (ctxt, tx_rollup) + (contract, ticket) + >>=? fun (ctxt, count) -> + match count with + | None -> return (ctxt, Z.zero) + | Some existing -> return (ctxt, existing) ) + >>=? fun (ctxt, existing) -> + let new_amount = Z.add existing (Z.of_int64 amount) in + Storage.Tx_rollup.Ticket_offramp.add + (ctxt, tx_rollup) + (contract, ticket) + new_amount + >|=? just_ctxt) + ctxt + effects) + ctxt + commitment.batches + +let retire_rollup_level : + Raw_context.t -> + Tx_rollup_repr.t -> + Raw_level_repr.t -> + Raw_level_repr.t -> + (Raw_context.t * bool) tzresult Lwt.t = + fun ctxt tx_rollup level last_level_to_finalize -> + let top = (Raw_context.current_level ctxt).level in + let key = (level, tx_rollup) in + get_or_empty_commitments ctxt key >>=? fun (ctxt, commitments) -> + let commitments = List.rev commitments in + match commitments with + | [] -> return (ctxt, false) + | accepted :: rejected -> + if Raw_level_repr.(accepted.submitted_at > last_level_to_finalize) then + return (ctxt, false) + else + let to_reject = + Commitment_set.of_seq + (Seq.map (fun {hash; _} -> hash) (List.to_seq rejected)) + in + remove_successors ctxt tx_rollup level top to_reject >>=? fun ctxt -> + reduce_commitment_bond ctxt tx_rollup accepted.committer + >>=? fun ctxt -> + apply_effects ctxt tx_rollup accepted.commitment >>=? fun ctxt -> + Storage.Tx_rollup.Commitment_list.add ctxt key [accepted] + >>=? fun (ctxt, _, _) -> return (ctxt, true) + +let get_commitments : + Raw_context.t -> + Tx_rollup_repr.t -> + Raw_level_repr.t -> + (Raw_context.t * Tx_rollup_commitments_repr.t) tzresult Lwt.t = + fun ctxt tx_rollup level -> + Storage.Tx_rollup.State.find ctxt tx_rollup >>=? fun (ctxt, state) -> + match state with + | None -> fail @@ Tx_rollup_state_storage.Tx_rollup_does_not_exist tx_rollup + | Some _ -> + Storage.Tx_rollup.Commitment_list.get ctxt (level, tx_rollup) + >|=? fun (ctxt, commitments) -> (ctxt, List.rev commitments) + +let pending_bonded_commitments : + Raw_context.t -> + Tx_rollup_repr.t -> + Contract_repr.t -> + (Raw_context.t * int) tzresult Lwt.t = + fun ctxt tx_rollup contract -> + Storage.Tx_rollup.Commitment_bond.find ctxt (tx_rollup, contract) + >|=? fun (ctxt, pending) -> + match pending with + | None -> (ctxt, 0) + | Some (commitments, _tez) -> (ctxt, commitments) + +let finalize_successful_prerejections ctxt tx_rollup level = + Storage.Tx_rollup.Successful_prerejections.list_values + ((ctxt, level), tx_rollup) + >>=? fun (ctxt, values) -> + (* TODO: clear this out -- we can't do that because there is no function + which will give us the list of keys, nor one which will remove everything + under a context. *) + return (ctxt, List.to_seq @@ List.map snd values) + +let finalize_pending_commitments ctxt tx_rollup = + Tx_rollup_state_storage.get ctxt tx_rollup >>=? fun (ctxt, state) -> + let first_unfinalized_level = + Tx_rollup_state_repr.first_unfinalized_level state + in + match first_unfinalized_level with + | None -> return (ctxt, []) + | Some first_unfinalized_level -> + let current_level = (Raw_context.current_level ctxt).level in + let last_level_to_finalize = + match Raw_level_repr.sub current_level 30 with + | Some level -> level + | None -> Raw_level_repr.root + in + let rec finalize_level ctxt level top count to_credit = + if Raw_level_repr.(level > top) then + return (ctxt, count, to_credit, Some level) + else + retire_rollup_level ctxt tx_rollup level last_level_to_finalize + >>=? fun (ctxt, finalized) -> + if not finalized then return (ctxt, 0, Seq.empty, Some level) + else + finalize_successful_prerejections ctxt tx_rollup level + >>=? fun (ctxt, new_to_credit) -> + let to_credit = Seq.append to_credit new_to_credit in + get_next_level ctxt tx_rollup level >>=? fun (ctxt, next_level) -> + match next_level with + | None -> return (ctxt, count, to_credit, None) + | Some next_level -> + finalize_level ctxt next_level top (count + 1) to_credit + in + finalize_level + ctxt + first_unfinalized_level + last_level_to_finalize + 0 + Seq.empty + >>=? fun (ctxt, finalized_count, to_credit, first_unfinalized_level) -> + let new_state = + Tx_rollup_state_repr.update_after_finalize + state + first_unfinalized_level + finalized_count + in + Storage.Tx_rollup.State.add ctxt tx_rollup new_state + >>=? fun (ctxt, _, _) -> return (ctxt, List.of_seq to_credit) + +let prereject : + Raw_context.t -> + Tx_rollup_rejection_repr.Rejection_hash.t -> + Raw_context.t tzresult Lwt.t = + fun ctxt hash -> + let current_level = (Raw_context.current_level ctxt).level in + (match Raw_level_repr.sub current_level 30 with + | Some gc_level -> gc_prerejections ctxt gc_level + | None -> return ctxt) + >>=? fun ctxt -> + Storage.Tx_rollup.Prerejection.mem ctxt hash >>=? fun (ctxt, is_mem) -> + fail_when is_mem Tx_rollup_rejection_repr.Duplicate_prerejection + >>=? fun () -> + (Storage.Tx_rollup.Prerejection_counter.find ctxt >>=? function + | None -> + Storage.Tx_rollup.Prerejection_counter.init ctxt Z.one >>=? fun ctxt -> + Storage.Tx_rollup.Oldest_prerejection.init ctxt Z.zero >>=? fun ctxt -> + return (ctxt, Z.zero) + | Some counter -> + Storage.Tx_rollup.Prerejection_counter.update ctxt (Z.succ counter) + >>=? fun ctxt -> return (ctxt, counter)) + >>=? fun (ctxt, counter) -> + Storage.Tx_rollup.Prerejection.add ctxt hash counter >>=? fun (ctxt, _, _) -> + Storage.Tx_rollup.Prerejection_by_index.add ctxt counter (hash, current_level) + >|=? just_ctxt + +let check_prerejection : + Raw_context.t -> + Tx_rollup_rejection_repr.t -> + int64 -> + Contract_repr.t -> + (Raw_context.t * Z.t * bool) tzresult Lwt.t = + fun ctxt {rollup; level; hash; batch_index; _} nonce source -> + let prerejection_hash = + Tx_rollup_rejection_repr.generate_prerejection + ~nonce + ~source + ~rollup + ~level + ~commitment_hash:hash + ~batch_index + in + Storage.Tx_rollup.Prerejection.find ctxt prerejection_hash + >>=? fun (ctxt, priority) -> + match priority with + | None -> fail Tx_rollup_rejection_repr.Rejection_without_prerejection + | Some priority -> + find_commitment_by_hash ctxt rollup level hash + >>=? fun (ctxt, maybe_commitment) -> + return (ctxt, priority, Option.is_some maybe_commitment) diff --git a/src/proto_alpha/lib_protocol/tx_rollup_commitments_storage.mli b/src/proto_alpha/lib_protocol/tx_rollup_commitments_storage.mli new file mode 100644 index 0000000000000000000000000000000000000000..6f56fafea46012cbbc0becca25f7b2ee3c22c82d --- /dev/null +++ b/src/proto_alpha/lib_protocol/tx_rollup_commitments_storage.mli @@ -0,0 +1,137 @@ +(*****************************************************************************) +(* *) +(* Open Source License *) +(* Copyright (c) 2021 Marigold *) +(* Copyright (c) 2021 Nomadic Labs *) +(* Copyright (c) 2021 Oxhead Alpha *) +(* *) +(* Permission is hereby granted, free of charge, to any person obtaining a *) +(* copy of this software and associated documentation files (the "Software"),*) +(* to deal in the Software without restriction, including without limitation *) +(* the rights to use, copy, modify, merge, publish, distribute, sublicense, *) +(* and/or sell copies of the Software, and to permit persons to whom the *) +(* Software is furnished to do so, subject to the following conditions: *) +(* *) +(* The above copyright notice and this permission notice shall be included *) +(* in all copies or substantial portions of the Software. *) +(* *) +(* THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR*) +(* IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, *) +(* FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL *) +(* THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER*) +(* LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING *) +(* FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER *) +(* DEALINGS IN THE SOFTWARE. *) +(* *) +(*****************************************************************************) + +(** This module introduces various functions to manipulate the storage related + to commitments for transaction rollups. *) + +(** [add_commitment context tx_rollup contract commitment] adds a + commitment to a rollup. It also increments the bonded commitment + count for the contract. *) +val add_commitment : + Raw_context.t -> + Tx_rollup_repr.t -> + Contract_repr.t -> + Tx_rollup_commitments_repr.Commitment.t -> + Tez_repr.t -> + Raw_context.t tzresult Lwt.t + +(** [remove_bond context tx_rollup contract] removes the bond for a + contract. This will fail if either the bond does not exist, or the + bond is currently in-use. *) +val remove_bond : + Raw_context.t -> + Tx_rollup_repr.t -> + Contract_repr.t -> + Raw_context.t tzresult Lwt.t + +(** [reject_commitment ctxt tx_rollup_repr level commitment_hash] + rejects a commitment with a given hash at a given level. All + successor commitments are removed, and any bonds associated with + them are removed. Some successor commitments might be from + different contracts, in which case, we recursively remove all + contracts from those contracts and their successors, and so forth. + *) +val reject_commitment : + Raw_context.t -> + Tx_rollup_repr.t -> + Raw_level_repr.t -> + Tx_rollup_commitments_repr.Commitment_hash.t -> + Contract_repr.t -> + Z.t -> + Raw_context.t tzresult Lwt.t + +(* [get_oldest_prerejection ctxt] is for testing only. It returns + the index of oldest prerejection that we have not yet + garbage-collected, or None if nobody has never submitted any + prerejections. *) +val get_oldest_prerejection : Raw_context.t -> Z.t option tzresult Lwt.t + +(** [retire_rollup_level context tx_rollup level] removes all data + associated with a level. It decrements the bonded commitment count + for any contracts whose commitments have been either accepted or + obviated (that is, neither accepted nor rejected). This is normally + used in finalization (during a Commitment operation) and is only + public for testing. *) +val retire_rollup_level : + Raw_context.t -> + Tx_rollup_repr.t -> + Raw_level_repr.t -> + Raw_level_repr.t -> + (Raw_context.t * bool) tzresult Lwt.t + +(** [get_commitments context tx_rollup level] returns the list of + non-rejected commitments for a rollup at a level, first-submitted + first. *) +val get_commitments : + Raw_context.t -> + Tx_rollup_repr.t -> + Raw_level_repr.t -> + (Raw_context.t * Tx_rollup_commitments_repr.t) tzresult Lwt.t + +(** [pending bonded_commitments ctxt tx_rollup contract] returns the + number of commitments that [contract] has made on [tx_rollup] that + are still pending (that is, still subject to rejection). *) +val pending_bonded_commitments : + Raw_context.t -> + Tx_rollup_repr.t -> + Contract_repr.t -> + (Raw_context.t * int) tzresult Lwt.t + +(** [finalize_pending_commitments ctxt tx_rollup] finalizes all + pending commitments that are old enough. *) +val finalize_pending_commitments : + Raw_context.t -> + Tx_rollup_repr.t -> + (Raw_context.t * Contract_repr.t list) tzresult Lwt.t + +(** [get_commitment_roots] Returns the before and after roots *) +val get_commitment_roots : + Raw_context.t -> + Tx_rollup_repr.t -> + Raw_level_repr.t -> + Tx_rollup_commitments_repr.Commitment_hash.t -> + int -> + (Raw_context.t + * (Tx_rollup_commitments_repr.Commitment.batch_commitment + * Tx_rollup_commitments_repr.Commitment.batch_commitment)) + tzresult + Lwt.t + +val prereject : + Raw_context.t -> + Tx_rollup_rejection_repr.Rejection_hash.t -> + Raw_context.t tzresult Lwt.t + +(** [check_prerejection ctxt rejection nonce] ensures that a prerejection + with this nonce from this contract exists. Returns the priority of the + prerejection. *) +val check_prerejection : + Raw_context.t -> + Tx_rollup_rejection_repr.t -> + int64 -> + Contract_repr.t -> + (Raw_context.t * Z.t * bool) tzresult Lwt.t diff --git a/src/proto_alpha/lib_protocol/tx_rollup_frozen_storage.ml b/src/proto_alpha/lib_protocol/tx_rollup_frozen_storage.ml new file mode 100644 index 0000000000000000000000000000000000000000..55123dfca5ec4425e447c99553aaf784b4d04bb4 --- /dev/null +++ b/src/proto_alpha/lib_protocol/tx_rollup_frozen_storage.ml @@ -0,0 +1,30 @@ +(*****************************************************************************) +(* *) +(* Open Source License *) +(* Copyright (c) 2022 Oxhead Alpha *) +(* *) +(* Permission is hereby granted, free of charge, to any person obtaining a *) +(* copy of this software and associated documentation files (the "Software"),*) +(* to deal in the Software without restriction, including without limitation *) +(* the rights to use, copy, modify, merge, publish, distribute, sublicense, *) +(* and/or sell copies of the Software, and to permit persons to whom the *) +(* Software is furnished to do so, subject to the following conditions: *) +(* *) +(* The above copyright notice and this permission notice shall be included *) +(* in all copies or substantial portions of the Software. *) +(* *) +(* THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR*) +(* IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, *) +(* FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL *) +(* THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER*) +(* LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING *) +(* FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER *) +(* DEALINGS IN THE SOFTWARE. *) +(* *) +(*****************************************************************************) + +let frozen_tez : Raw_context.t -> Contract_repr.t -> Tez_repr.t tzresult Lwt.t = + fun ctxt contract -> + Storage.Tx_rollup.Frozen_commitments.find ctxt contract >>=? function + | None -> return Tez_repr.zero + | Some tez -> return tez diff --git a/src/proto_alpha/lib_protocol/tx_rollup_frozen_storage.mli b/src/proto_alpha/lib_protocol/tx_rollup_frozen_storage.mli new file mode 100644 index 0000000000000000000000000000000000000000..fc3fb1656aea04aabfa959a79486da9d4e1b133b --- /dev/null +++ b/src/proto_alpha/lib_protocol/tx_rollup_frozen_storage.mli @@ -0,0 +1,32 @@ +(*****************************************************************************) +(* *) +(* Open Source License *) +(* Copyright (c) 2022 Oxhead Alpha *) +(* *) +(* Permission is hereby granted, free of charge, to any person obtaining a *) +(* copy of this software and associated documentation files (the "Software"),*) +(* to deal in the Software without restriction, including without limitation *) +(* the rights to use, copy, modify, merge, publish, distribute, sublicense, *) +(* and/or sell copies of the Software, and to permit persons to whom the *) +(* Software is furnished to do so, subject to the following conditions: *) +(* *) +(* The above copyright notice and this permission notice shall be included *) +(* in all copies or substantial portions of the Software. *) +(* *) +(* THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR*) +(* IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, *) +(* FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL *) +(* THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER*) +(* LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING *) +(* FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER *) +(* DEALINGS IN THE SOFTWARE. *) +(* *) +(*****************************************************************************) + +(** This module introduces various functions to manipulate the storage related + to transaction rollup bonds -- it's in a separate file for dependency + reasons. *) + +(** [frozen_tez ctxt contract] returns the total tez in all commitments + for a given contract. *) +val frozen_tez : Raw_context.t -> Contract_repr.t -> Tez_repr.t tzresult Lwt.t diff --git a/src/proto_alpha/lib_protocol/tx_rollup_inbox_storage.ml b/src/proto_alpha/lib_protocol/tx_rollup_inbox_storage.ml index f7d287876ad1e2a56a4eb8446e9458bad53cf744..158c55790838003dedd5f1a3881d27d70db1cf0b 100644 --- a/src/proto_alpha/lib_protocol/tx_rollup_inbox_storage.ml +++ b/src/proto_alpha/lib_protocol/tx_rollup_inbox_storage.ml @@ -43,6 +43,11 @@ let prepare_metadata : tzresult Lwt.t = fun ctxt rollup state level -> + (* First, check if there are too many unfinalized levels. *) + fail_when + Compare.Int.(Tx_rollup_state_repr.unfinalized_level_count state > 100) + Tx_rollup_commitments_repr.Too_many_unfinalized_levels + >>=? fun () -> Storage.Tx_rollup.Inbox_metadata.find (ctxt, level) rollup >>=? fun (ctxt, metadata) -> match metadata with @@ -52,6 +57,10 @@ let prepare_metadata : inbox count *) let predecessor = Tx_rollup_state_repr.last_inbox_level state in let new_state = Tx_rollup_state_repr.append_inbox state level in + let new_state = + Tx_rollup_state_repr.increment_unfinalized_level_count new_state + in + Tx_rollup_state_storage.update ctxt rollup new_state >>=? fun ctxt -> (match predecessor with | None -> return ctxt | Some predecessor_level -> diff --git a/src/proto_alpha/lib_protocol/tx_rollup_message_repr.ml b/src/proto_alpha/lib_protocol/tx_rollup_message_repr.ml index a0a0fbe7d426f3f5ec9c63f273919b90524432e8..e2aef4707300e2d45ee0234269017e59883f6515 100644 --- a/src/proto_alpha/lib_protocol/tx_rollup_message_repr.ml +++ b/src/proto_alpha/lib_protocol/tx_rollup_message_repr.ml @@ -128,3 +128,25 @@ let hash_encoding = Message_hash.encoding let hash msg = Message_hash.hash_bytes [Data_encoding.Binary.to_bytes_exn encoding msg] + +include Compare.Make (struct + type nonrec t = t + + let compare_deposit + {destination = destination1; ticket_hash = ticket_hash1; amount = amount1} + {destination = destination2; ticket_hash = ticket_hash2; amount = amount2} + = + match Tx_rollup_l2_address.Indexable.compare destination1 destination2 with + | 0 -> ( + match Ticket_hash_repr.compare ticket_hash1 ticket_hash2 with + | 0 -> Compare.Int64.compare amount1 amount2 + | c -> c) + | c -> c + + let compare m1 m2 = + match (m1, m2) with + | (Batch s, Batch t) -> String.compare s t + | (Batch _, Deposit _) -> -1 + | (Deposit _, Batch _) -> 1 + | (Deposit d, Deposit e) -> compare_deposit d e +end) diff --git a/src/proto_alpha/lib_protocol/tx_rollup_message_repr.mli b/src/proto_alpha/lib_protocol/tx_rollup_message_repr.mli index 270e5984966aeb86414cc53f806a4585fe183aab..df673739a574b838cc65cce2a1525eba748d6dff 100644 --- a/src/proto_alpha/lib_protocol/tx_rollup_message_repr.mli +++ b/src/proto_alpha/lib_protocol/tx_rollup_message_repr.mli @@ -74,3 +74,5 @@ val pp_hash : Format.formatter -> hash -> unit (** [hash msg] computes the hash of [msg] to be stored in the inbox. *) val hash : t -> hash + +include Compare.S with type t := t diff --git a/src/proto_alpha/lib_protocol/tx_rollup_offramp_storage.ml b/src/proto_alpha/lib_protocol/tx_rollup_offramp_storage.ml new file mode 100644 index 0000000000000000000000000000000000000000..0fabb38251b2de0531fd3d37279fedcdd3dd71f3 --- /dev/null +++ b/src/proto_alpha/lib_protocol/tx_rollup_offramp_storage.ml @@ -0,0 +1,70 @@ +(*****************************************************************************) +(* *) +(* Open Source License *) +(* Copyright (c) 2022 Marigold *) +(* Copyright (c) 2022 Nomadic Labs *) +(* Copyright (c) 2022 Oxhead Alpha *) +(* *) +(* Permission is hereby granted, free of charge, to any person obtaining a *) +(* copy of this software and associated documentation files (the "Software"),*) +(* to deal in the Software without restriction, including without limitation *) +(* the rights to use, copy, modify, merge, publish, distribute, sublicense, *) +(* and/or sell copies of the Software, and to permit persons to whom the *) +(* Software is furnished to do so, subject to the following conditions: *) +(* *) +(* The above copyright notice and this permission notice shall be included *) +(* in all copies or substantial portions of the Software. *) +(* *) +(* THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR*) +(* IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, *) +(* FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL *) +(* THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER*) +(* LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING *) +(* FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER *) +(* DEALINGS IN THE SOFTWARE. *) +(* *) +(*****************************************************************************) + +type error += (* `Permanent *) Withdraw_balance_too_low + +let withdraw ctxt tx_rollup contract ~rollup_ticket_hash + ~destination_ticket_hash (count : int64) = + let count = Z.of_int64 count in + let key = (ctxt, tx_rollup) in + ( Storage.Tx_rollup.Ticket_offramp.get key (contract, rollup_ticket_hash) + >>=? fun (ctxt, remaining) -> + let key = (ctxt, tx_rollup) in + let cmp = Z.compare remaining count in + match cmp with + | 0 -> + Storage.Tx_rollup.Ticket_offramp.remove + key + (contract, rollup_ticket_hash) + | 1 -> + let balance = Z.sub remaining count in + Storage.Tx_rollup.Ticket_offramp.add + key + (contract, rollup_ticket_hash) + balance + | _ -> fail Withdraw_balance_too_low ) + >>=? fun (ctxt, _, _) -> + (* TODO: https://gitlab.com/tezos/tezos/-/issues/2339 + Storage fees for transaction rollup. + We need to charge for newly allocated storage (as we do for + Michelson’s big map). This also means taking into account + the global table of tickets. *) + Ticket_storage.adjust_balance ctxt rollup_ticket_hash ~delta:(Z.neg count) + >>=? fun (_, ctxt) -> + Ticket_storage.adjust_balance ctxt destination_ticket_hash ~delta:count + >>=? fun (_, ctxt) -> return ctxt + +let add_tickets_to_offramp ctxt tx_rollup contract ticket (count : int64) = + let count = Z.of_int64 count in + let key = (ctxt, tx_rollup) in + Storage.Tx_rollup.Ticket_offramp.find key (contract, ticket) + >>=? fun (ctxt, existing) -> + let existing = Option.value ~default:Z.zero existing in + let new_balance = Z.add existing count in + let key = (ctxt, tx_rollup) in + Storage.Tx_rollup.Ticket_offramp.add key (contract, ticket) new_balance + >|=? fun (ctxt, _, _) -> ctxt diff --git a/src/proto_alpha/lib_protocol/tx_rollup_offramp_storage.mli b/src/proto_alpha/lib_protocol/tx_rollup_offramp_storage.mli new file mode 100644 index 0000000000000000000000000000000000000000..37029853f1ced62dc9899b62deb9ed531bfaa319 --- /dev/null +++ b/src/proto_alpha/lib_protocol/tx_rollup_offramp_storage.mli @@ -0,0 +1,52 @@ +(*****************************************************************************) +(* *) +(* Open Source License *) +(* Copyright (c) 2022 Marigold *) +(* Copyright (c) 2022 Nomadic Labs *) +(* Copyright (c) 2022 Oxhead Alpha *) +(* *) +(* Permission is hereby granted, free of charge, to any person obtaining a *) +(* copy of this software and associated documentation files (the "Software"),*) +(* to deal in the Software without restriction, including without limitation *) +(* the rights to use, copy, modify, merge, publish, distribute, sublicense, *) +(* and/or sell copies of the Software, and to permit persons to whom the *) +(* Software is furnished to do so, subject to the following conditions: *) +(* *) +(* The above copyright notice and this permission notice shall be included *) +(* in all copies or substantial portions of the Software. *) +(* *) +(* THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR*) +(* IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, *) +(* FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL *) +(* THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER*) +(* LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING *) +(* FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER *) +(* DEALINGS IN THE SOFTWARE. *) +(* *) +(*****************************************************************************) + +type error += (* `Permanent *) Withdraw_balance_too_low + +(** [withdraw ctxt tx_rollup contract ticket_hash amount] withdraws tickets + tickets from a rollup and transfers them to the given contract. It + fails if the balance in the offramp for this commitment is too low. *) +val withdraw : + Raw_context.t -> + Tx_rollup_repr.t -> + Contract_repr.t -> + rollup_ticket_hash:Ticket_hash_repr.t -> + destination_ticket_hash:Ticket_hash_repr.t -> + int64 -> + Raw_context.t tzresult Lwt.t + +(** [add_tickets_to_offramp ctxt tx_rollup contract ticket_hash amount] + prepares tickets for withdrawal by adding them to the offramp. This + should only be called when resolving a L2 withdraw operation. + *) +val add_tickets_to_offramp : + Raw_context.t -> + Tx_rollup_repr.t -> + Contract_repr.t -> + Ticket_hash_repr.t -> + int64 -> + Raw_context.t tzresult Lwt.t diff --git a/src/proto_alpha/lib_protocol/tx_rollup_rejection_repr.ml b/src/proto_alpha/lib_protocol/tx_rollup_rejection_repr.ml new file mode 100644 index 0000000000000000000000000000000000000000..291bc5df75774b8eb7dcca42ca0b8fe2ef1546c1 --- /dev/null +++ b/src/proto_alpha/lib_protocol/tx_rollup_rejection_repr.ml @@ -0,0 +1,206 @@ +(*****************************************************************************) +(* *) +(* Open Source License *) +(* Copyright (c) 2022 Marigold *) +(* Copyright (c) 2022 Nomadic Labs *) +(* Copyright (c) 2022 Oxhead Alpha *) +(* *) +(* Permission is hereby granted, free of charge, to any person obtaining a *) +(* copy of this software and associated documentation files (the "Software"),*) +(* to deal in the Software without restriction, including without limitation *) +(* the rights to use, copy, modify, merge, publish, distribute, sublicense, *) +(* and/or sell copies of the Software, and to permit persons to whom the *) +(* Software is furnished to do so, subject to the following conditions: *) +(* *) +(* The above copyright notice and this permission notice shall be included *) +(* in all copies or substantial portions of the Software. *) +(* *) +(* THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR*) +(* IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, *) +(* FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL *) +(* THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER*) +(* LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING *) +(* FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER *) +(* DEALINGS IN THE SOFTWARE. *) +(* *) +(*****************************************************************************) + +type error += (* `Permanent *) Wrong_rejection + +type error += (* `Permanent *) Rejection_without_prerejection + +type error += (* `Permanent *) Duplicate_prerejection + +let () = + let open Data_encoding in + (* Wrong_rejection *) + register_error_kind + `Temporary + ~id:"Wrong_rejection" + ~title:"This rejection wrongly attempts to reject a correct comitment" + ~description:"This rejection wrongly attempts to reject a correct comitment" + unit + (function Wrong_rejection -> Some () | _ -> None) + (fun () -> Wrong_rejection) ; + (* Rejection_without_prerejection *) + register_error_kind + `Temporary + ~id:"Rejection_without_prerejection" + ~title:"This rejection is missing a prerejection" + ~description:"This rejection is missing a prerejection" + unit + (function Rejection_without_prerejection -> Some () | _ -> None) + (fun () -> Rejection_without_prerejection) ; + (* Duplicate_prerejection *) + register_error_kind + `Temporary + ~id:"Duplicate_prerejection" + ~title:"This prerejection has already been filed" + ~description:"This prerejection has already been filed" + unit + (function Duplicate_prerejection -> Some () | _ -> None) + (fun () -> Duplicate_prerejection) + +type t = { + rollup : Tx_rollup_repr.t; + level : Raw_level_repr.t; + hash : Tx_rollup_commitments_repr.Commitment_hash.t; + batch_index : int; + batch : Tx_rollup_message_repr.t; +} + +let encoding = + let open Data_encoding in + conv + (fun {rollup; level; hash; batch_index; batch} -> + (rollup, level, hash, batch_index, batch)) + (fun (rollup, level, hash, batch_index, batch) -> + {rollup; level; hash; batch_index; batch}) + (obj5 + (req "rollup" Tx_rollup_repr.encoding) + (req "level" Raw_level_repr.encoding) + (req "hash" Tx_rollup_commitments_repr.Commitment_hash.encoding) + (req "batch_index" int31) + (req "batch" Tx_rollup_message_repr.encoding)) + +include Compare.Make (struct + type nonrec t = t + + let compare + { + rollup = rollup1; + level = level1; + hash = hash1; + batch_index = batch_index1; + batch = batch1; + } + { + rollup = rollup2; + level = level2; + hash = hash2; + batch_index = batch_index2; + batch = batch2; + } = + match Tx_rollup_repr.compare rollup1 rollup2 with + | 0 -> ( + match Raw_level_repr.compare level1 level2 with + | 0 -> ( + match + Tx_rollup_commitments_repr.Commitment_hash.compare hash1 hash2 + with + | 0 -> ( + match Compare.Int.compare batch_index1 batch_index2 with + | 0 -> Tx_rollup_message_repr.compare batch1 batch2 + | c -> c) + | c -> c) + | c -> c) + | c -> c +end) + +module Rejection_hash = struct + let rejection_hash = "\001\111\092\025" (* rej1(37) *) + + module H = + Blake2B.Make + (Base58) + (struct + let name = "Rejection_hash" + + let title = "A rejection ID" + + let b58check_prefix = rejection_hash + + let size = Some 20 + end) + + include H + + let () = Base58.check_encoded_prefix b58check_encoding "rej1" 37 + + include Path_encoding.Make_hex (H) + + let rpc_arg = + let construct = Data_encoding.Binary.to_string_exn encoding in + let destruct str = + Option.value_e ~error:"Failed to decode rejection" + @@ Data_encoding.Binary.of_string_opt encoding str + in + RPC_arg.make + ~descr:"A tx_rollup rejection." + ~name:"tx_rollup_rejection" + ~construct + ~destruct + () + + module Index = struct + type nonrec t = t + + let path_length = 1 + + let to_path c l = + let raw_key = Data_encoding.Binary.to_bytes_exn encoding c in + let (`Hex key) = Hex.of_bytes raw_key in + key :: l + + let of_path = function + | [key] -> + Option.bind + (Hex.to_bytes (`Hex key)) + (Data_encoding.Binary.of_bytes_opt encoding) + | _ -> None + + let rpc_arg = rpc_arg + + let encoding = encoding + + let compare = compare + end +end + +let generate_prerejection : + nonce:int64 -> + source:Contract_repr.t -> + rollup:Tx_rollup_repr.t -> + level:Raw_level_repr.t -> + commitment_hash:Tx_rollup_commitments_repr.Commitment_hash.t -> + batch_index:int -> + Rejection_hash.t = + fun ~nonce ~source ~rollup ~level ~commitment_hash ~batch_index -> + let to_bytes = Data_encoding.Binary.to_bytes_exn in + let rollup_bytes = to_bytes Tx_rollup_repr.encoding rollup in + let level_bytes = to_bytes Raw_level_repr.encoding level in + let hash_bytes = + Tx_rollup_commitments_repr.Commitment_hash.to_bytes commitment_hash + in + let batch_index_bytes = to_bytes Data_encoding.int31 batch_index in + let nonce_bytes = Bytes.of_string @@ Int64.to_string nonce in + let contract_bytes = to_bytes Contract_repr.encoding source in + Rejection_hash.hash_bytes + [ + rollup_bytes; + level_bytes; + nonce_bytes; + hash_bytes; + batch_index_bytes; + contract_bytes; + ] diff --git a/src/proto_alpha/lib_protocol/tx_rollup_rejection_repr.mli b/src/proto_alpha/lib_protocol/tx_rollup_rejection_repr.mli new file mode 100644 index 0000000000000000000000000000000000000000..d291feb060c1cb24c7ce6fd5a9f2bcbaff2dcd39 --- /dev/null +++ b/src/proto_alpha/lib_protocol/tx_rollup_rejection_repr.mli @@ -0,0 +1,61 @@ +(*****************************************************************************) +(* *) +(* Open Source License *) +(* Copyright (c) 2022 Marigold *) +(* Copyright (c) 2022 Nomadic Labs *) +(* Copyright (c) 2022 Oxhead Alpha *) +(* *) +(* Permission is hereby granted, free of charge, to any person obtaining a *) +(* copy of this software and associated documentation files (the "Software"),*) +(* to deal in the Software without restriction, including without limitation *) +(* the rights to use, copy, modify, merge, publish, distribute, sublicense, *) +(* and/or sell copies of the Software, and to permit persons to whom the *) +(* Software is furnished to do so, subject to the following conditions: *) +(* *) +(* The above copyright notice and this permission notice shall be included *) +(* in all copies or substantial portions of the Software. *) +(* *) +(* THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR*) +(* IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, *) +(* FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL *) +(* THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER*) +(* LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING *) +(* FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER *) +(* DEALINGS IN THE SOFTWARE. *) +(* *) +(*****************************************************************************) + +type error += (* `Permanent *) Wrong_rejection + +type error += (* `Permanent *) Rejection_without_prerejection + +type error += (* `Permanent *) Duplicate_prerejection + +type t = { + rollup : Tx_rollup_repr.t; + level : Raw_level_repr.t; + hash : Tx_rollup_commitments_repr.Commitment_hash.t; + batch_index : int; + batch : Tx_rollup_message_repr.t; +} + +val encoding : t Data_encoding.t + +module Rejection_hash : sig + val rejection_hash : string + + include S.HASH + + module Index : Storage_description.INDEX with type t = t +end + +val generate_prerejection : + nonce:int64 -> + source:Contract_repr.t -> + rollup:Tx_rollup_repr.t -> + level:Raw_level_repr.t -> + commitment_hash:Tx_rollup_commitments_repr.Commitment_hash.t -> + batch_index:int -> + Rejection_hash.t + +include Compare.S with type t := t diff --git a/src/proto_alpha/lib_protocol/tx_rollup_repr.ml b/src/proto_alpha/lib_protocol/tx_rollup_repr.ml index 42cdb07049404bd3f697985e2b636e926b36f08a..8b1fbbcb2f3da6f3bd3bd1df83fcca6ce5b17daa 100644 --- a/src/proto_alpha/lib_protocol/tx_rollup_repr.ml +++ b/src/proto_alpha/lib_protocol/tx_rollup_repr.ml @@ -40,6 +40,8 @@ let () = (function Invalid_rollup_notation loc -> Some loc | _ -> None) (fun loc -> Invalid_rollup_notation loc) +let hash_size = 20 + module Hash = struct let rollup_hash = "\001\127\181\221" (* tru1(37) *) @@ -53,7 +55,7 @@ module Hash = struct let b58check_prefix = rollup_hash - let size = Some 20 + let size = Some hash_size end) include H @@ -73,6 +75,10 @@ include Compare.Make (struct let compare r1 r2 = Hash.compare r1 r2 end) +let in_memory_size _ = + let open Cache_memory_helpers in + header_size +! word_size +! string_size_gen hash_size + let to_b58check rollup = Hash.to_b58check rollup let of_b58check_opt s = @@ -145,3 +151,23 @@ module Index = struct let compare = compare end + +let deposit_entrypoint = Entrypoint_repr.of_string_strict_exn "deposit" + +type deposit_parameters = { + contents : Script_repr.node; + ty : Script_repr.node; + ticketer : Script_repr.node; + amount : int64; + destination : Tx_rollup_l2_address.Indexable.t; +} + +let withdraw_entrypoint = Entrypoint_repr.of_string_strict_exn "withdraw" + +type withdraw_parameters = { + contents : Script_repr.node; + ty : Script_repr.node; + ticketer : Script_repr.node; + amount : int64; + destination_contract : Contract_repr.t; +} diff --git a/src/proto_alpha/lib_protocol/tx_rollup_repr.mli b/src/proto_alpha/lib_protocol/tx_rollup_repr.mli index 552faf192e05b944f6f0e25113f77515241e63e2..bb3cf48eb1eeb429a0eaf162c403a6742ef7c00d 100644 --- a/src/proto_alpha/lib_protocol/tx_rollup_repr.mli +++ b/src/proto_alpha/lib_protocol/tx_rollup_repr.mli @@ -42,6 +42,10 @@ type tx_rollup = t include Compare.S with type t := t +(** [in_memory_size tx_rollup] returns the number of bytes [tx_rollup] + uses in RAM. *) +val in_memory_size : t -> Cache_memory_helpers.sint + val to_b58check : t -> string val of_b58check : string -> t tzresult @@ -59,3 +63,32 @@ val originated_tx_rollup : Origination_nonce.t -> t val rpc_arg : t RPC_arg.arg module Index : Storage_description.INDEX with type t = t + +(** The entrypoint a layer-1 contract can use to deposit Michelson tickets + into a transaction rollup. *) +val deposit_entrypoint : Entrypoint_repr.t + +(** The parameters expected to be supplied to the deposit entrypoint. + + These arguments will not be supplied as-is, but encoded using + Micheline. + + The function {!Script_ir_translator.parse_tx_rollup_deposit_parameters} + should be used to extract a [deposit_parameters] from a Micheline value. *) +type deposit_parameters = { + contents : Script_repr.node; + ty : Script_repr.node; + ticketer : Script_repr.node; + amount : int64; + destination : Tx_rollup_l2_address.Indexable.t; +} + +val withdraw_entrypoint : Entrypoint_repr.t + +type withdraw_parameters = { + contents : Script_repr.node; + ty : Script_repr.node; + ticketer : Script_repr.node; + amount : int64; + destination_contract : Contract_repr.t; +} diff --git a/src/proto_alpha/lib_protocol/tx_rollup_services.ml b/src/proto_alpha/lib_protocol/tx_rollup_services.ml index ea51929bbd0b0ab9347c566be73b4f5fc6dc8c2d..dbf1b21d702b0822b21077265aa3e502cd2a0fe8 100644 --- a/src/proto_alpha/lib_protocol/tx_rollup_services.ml +++ b/src/proto_alpha/lib_protocol/tx_rollup_services.ml @@ -44,6 +44,13 @@ module S = struct ~query:RPC_query.empty ~output:Tx_rollup_inbox.encoding RPC_path.(custom_root /: Tx_rollup.rpc_arg / "inbox") + + let commitments = + RPC_service.get_service + ~description:"." + ~query:RPC_query.empty + ~output:Tx_rollup_commitments.encoding + RPC_path.(custom_root /: Tx_rollup.rpc_arg / "commitments") end let register () = @@ -51,10 +58,16 @@ let register () = opt_register1 ~chunked:false S.state (fun ctxt tx_rollup () () -> Tx_rollup_state.find ctxt tx_rollup >|=? snd) ; opt_register1 ~chunked:false S.inbox (fun ctxt tx_rollup () () -> - Tx_rollup_inbox.find ctxt tx_rollup ~level:`Current >|=? snd) + Tx_rollup_inbox.find ctxt tx_rollup ~level:`Current >|=? snd) ; + register1 ~chunked:false S.commitments (fun ctxt tx_rollup () () -> + let level = (Level.current ctxt).level in + Tx_rollup_commitments.get_commitments ctxt tx_rollup level >|=? snd) let state ctxt block tx_rollup = RPC_context.make_call1 S.state ctxt block tx_rollup () () let inbox ctxt block tx_rollup = RPC_context.make_call1 S.inbox ctxt block tx_rollup () () + +let commitments ctxt block tx_rollup = + RPC_context.make_call1 S.commitments ctxt block tx_rollup () () diff --git a/src/proto_alpha/lib_protocol/tx_rollup_services.mli b/src/proto_alpha/lib_protocol/tx_rollup_services.mli index 3e4f932d703c649bd0a907a374de8c52f182be1e..d881aa5b9689f401a7680c2d244ec1b107e102e3 100644 --- a/src/proto_alpha/lib_protocol/tx_rollup_services.mli +++ b/src/proto_alpha/lib_protocol/tx_rollup_services.mli @@ -43,4 +43,10 @@ val inbox : Tx_rollup.t -> Tx_rollup_inbox.t shell_tzresult Lwt.t +val commitments : + 'a #RPC_context.simple -> + 'a -> + Tx_rollup.t -> + Tx_rollup_commitments.t shell_tzresult Lwt.t + val register : unit -> unit diff --git a/src/proto_alpha/lib_protocol/tx_rollup_state_repr.ml b/src/proto_alpha/lib_protocol/tx_rollup_state_repr.ml index 52bdce08d5e37e0ef99483c30d2a8a9a4846e05d..bd00cc2dfab4cead763a538bd97823016ff5d3b9 100644 --- a/src/proto_alpha/lib_protocol/tx_rollup_state_repr.ml +++ b/src/proto_alpha/lib_protocol/tx_rollup_state_repr.ml @@ -26,25 +26,63 @@ (*****************************************************************************) type t = { + first_unfinalized_level : Raw_level_repr.t option; + unfinalized_level_count : int; fees_per_byte : Tez_repr.t; last_inbox_level : Raw_level_repr.t option; } -let initial_state = {fees_per_byte = Tez_repr.zero; last_inbox_level = None} +let initial_state = + { + first_unfinalized_level = None; + unfinalized_level_count = 0; + fees_per_byte = Tez_repr.zero; + last_inbox_level = None; + } let encoding : t Data_encoding.t = let open Data_encoding in conv - (fun {last_inbox_level; fees_per_byte} -> (last_inbox_level, fees_per_byte)) - (fun (last_inbox_level, fees_per_byte) -> {last_inbox_level; fees_per_byte}) - (obj2 - (req "last_inbox_level" (option Raw_level_repr.encoding)) - (req "fees_per_byte" Tez_repr.encoding)) + (fun { + first_unfinalized_level; + unfinalized_level_count; + fees_per_byte; + last_inbox_level; + } -> + ( first_unfinalized_level, + unfinalized_level_count, + fees_per_byte, + last_inbox_level )) + (fun ( first_unfinalized_level, + unfinalized_level_count, + fees_per_byte, + last_inbox_level ) -> + { + first_unfinalized_level; + unfinalized_level_count; + fees_per_byte; + last_inbox_level; + }) + (obj4 + (req "first_unfinalized_level" (option Raw_level_repr.encoding)) + (req "unfinalized_level_count" int16) + (req "fees_per_byte" Tez_repr.encoding) + (req "last_inbox_level" (option Raw_level_repr.encoding))) -let pp fmt {fees_per_byte; last_inbox_level} = +let pp fmt + { + first_unfinalized_level; + unfinalized_level_count; + fees_per_byte; + last_inbox_level; + } = Format.fprintf fmt - "Tx_rollup: fees_per_byte = %a; last_inbox_level = %a" + "first_unfinalized_level %a unfinalized_level_count %d cost_per_byte: %a \ + newest inbox %a" + (Format.pp_print_option Raw_level_repr.pp) + first_unfinalized_level + unfinalized_level_count Tez_repr.pp fees_per_byte (Format.pp_print_option Raw_level_repr.pp) @@ -92,9 +130,77 @@ let fees {fees_per_byte; _} size = Tez_repr.(fees_per_byte *? Int64.of_int size) let last_inbox_level {last_inbox_level; _} = last_inbox_level -let append_inbox t level = {t with last_inbox_level = Some level} +let append_inbox t level = + { + t with + last_inbox_level = Some level; + first_unfinalized_level = + Some (Option.value ~default:level t.first_unfinalized_level); + } + +let unfinalized_level_count {unfinalized_level_count; _} = + unfinalized_level_count + +let first_unfinalized_level {first_unfinalized_level; _} = + first_unfinalized_level + +let increment_unfinalized_level_count state = + {state with unfinalized_level_count = state.unfinalized_level_count + 1} + +let update_after_finalize state level count = + { + state with + first_unfinalized_level = level; + unfinalized_level_count = state.unfinalized_level_count - count; + } module Internal_for_tests = struct let initial_state_with_fees_per_byte : Tez_repr.t -> t = - fun fees_per_byte -> {fees_per_byte; last_inbox_level = None} + fun fees_per_byte -> + { + first_unfinalized_level = None; + unfinalized_level_count = 0; + fees_per_byte; + last_inbox_level = None; + } end + +include Compare.Make (struct + type nonrec t = t + + let compare + { + first_unfinalized_level = first_unfinalized_level1; + unfinalized_level_count = unfinalized_level_count1; + fees_per_byte = fees_per_byte1; + last_inbox_level = last_inbox_level1; + } + { + first_unfinalized_level = first_unfinalized_level2; + unfinalized_level_count = unfinalized_level_count2; + fees_per_byte = fees_per_byte2; + last_inbox_level = last_inbox_level2; + } = + match Tez_repr.compare fees_per_byte1 fees_per_byte2 with + | 0 -> ( + match + Option.compare + Raw_level_repr.compare + first_unfinalized_level1 + first_unfinalized_level2 + with + | 0 -> ( + match + Compare.Int.compare + unfinalized_level_count1 + unfinalized_level_count2 + with + | 0 -> + Option.compare + Raw_level_repr.compare + last_inbox_level1 + last_inbox_level2 + | c -> c) + | c -> c) + | c -> c +end) diff --git a/src/proto_alpha/lib_protocol/tx_rollup_state_repr.mli b/src/proto_alpha/lib_protocol/tx_rollup_state_repr.mli index efac9d54d6531491c030dcef6c684755e9c79f00..8b8a628d8d5f1b3d64935a861e2979cc7d1f76b9 100644 --- a/src/proto_alpha/lib_protocol/tx_rollup_state_repr.mli +++ b/src/proto_alpha/lib_protocol/tx_rollup_state_repr.mli @@ -63,8 +63,29 @@ val last_inbox_level : t -> Raw_level_repr.t option [state] when messages have been added at a level. *) val append_inbox : t -> Raw_level_repr.t -> t +(** [unfinalized_level_count state] returns the number of unfinalized + levels of the rollup. If this is too high, we stop appending + messages until commitments catch up. *) +val unfinalized_level_count : t -> int + +(** [first_unfinalized_level state] returns the first unfinalized + level of the rollup. Note that this level might be empty.*) +val first_unfinalized_level : t -> Raw_level_repr.t option + +(* [increment_unfinalized_level_count state] increments the unfinalized + level count of a state -- it's called when the first message for a + level is added. *) +val increment_unfinalized_level_count : t -> t + +(* [update_after_finalize state level count] updates a state + after some levels have been finalized. [count] is the number of + finalized levels *) +val update_after_finalize : t -> Raw_level_repr.t option -> int -> t + module Internal_for_tests : sig (** [initial_state_with_fees_per_byte fees] returns [initial_state], but wherein it costs [fees] per byte to add a message to an inbox. *) val initial_state_with_fees_per_byte : Tez_repr.t -> t end + +include Compare.S with type t := t diff --git a/src/proto_alpha/lib_protocol/tx_rollup_state_storage.ml b/src/proto_alpha/lib_protocol/tx_rollup_state_storage.ml index ff9921d52efdb64bd5ab3fd89ec801745e09b4d4..9f8ed228492fee06f2b723cc15ba73eab7e13ac2 100644 --- a/src/proto_alpha/lib_protocol/tx_rollup_state_storage.ml +++ b/src/proto_alpha/lib_protocol/tx_rollup_state_storage.ml @@ -107,3 +107,11 @@ let () = (obj1 (req "rollup_address" Tx_rollup_repr.encoding)) (function Tx_rollup_does_not_exist rollup -> Some rollup | _ -> None) (fun rollup -> Tx_rollup_does_not_exist rollup) + +let first_unfinalized_level : + Raw_context.t -> + Tx_rollup_repr.t -> + (Raw_context.t * Raw_level_repr.t option) tzresult Lwt.t = + fun ctxt tx_rollup -> + Storage.Tx_rollup.State.get ctxt tx_rollup >>=? fun (ctxt, state) -> + return (ctxt, Tx_rollup_state_repr.first_unfinalized_level state) diff --git a/src/proto_alpha/lib_protocol/tx_rollup_state_storage.mli b/src/proto_alpha/lib_protocol/tx_rollup_state_storage.mli index aa313fcad784df0340a8da8c4d70549833fed2f3..ff6a981f2e89a990de3fc3338b15a0f6ef1f1972 100644 --- a/src/proto_alpha/lib_protocol/tx_rollup_state_storage.mli +++ b/src/proto_alpha/lib_protocol/tx_rollup_state_storage.mli @@ -80,3 +80,11 @@ val update : transaction rollup address. *) val assert_exist : Raw_context.t -> Tx_rollup_repr.t -> Raw_context.t tzresult Lwt.t + +(** [first_unfinalized_level] returns the first unfinalized level + of [tx_rollup]. If None, then there are no unfinalized levels + with inboxes. *) +val first_unfinalized_level : + Raw_context.t -> + Tx_rollup_repr.t -> + (Raw_context.t * Raw_level_repr.t option) tzresult Lwt.t diff --git a/tests_python/tests_alpha/test_mockup.py b/tests_python/tests_alpha/test_mockup.py index 1519c1de5d9ad061fdf6ed980f94b3aa3505ba5e..41bdaefb3653f1454d281d47f23a5d6ed87c1c4d 100644 --- a/tests_python/tests_alpha/test_mockup.py +++ b/tests_python/tests_alpha/test_mockup.py @@ -659,6 +659,7 @@ def _test_create_mockup_init_show_roundtrip( "tx_rollup_origination_size": 30_000, "tx_rollup_hard_size_limit_per_inbox": 75_000, "tx_rollup_hard_size_limit_per_message": 9_999, + "tx_rollup_commitment_bond": "10000000000", "sc_rollup_enable": False, "sc_rollup_origination_size": 6_314, } diff --git a/tezt/_regressions/rpc/alpha.client.mempool.out b/tezt/_regressions/rpc/alpha.client.mempool.out index 14db1d7e7cbd560b712eb286446963ae20fecd46..e55f42eb207fe6b2c1350a8b7227f29026324f0e 100644 --- a/tezt/_regressions/rpc/alpha.client.mempool.out +++ b/tezt/_regressions/rpc/alpha.client.mempool.out @@ -577,6 +577,10 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "additionalProperties": false }, "definitions": { + "Commitment_hash": { + "title": "A commitment ID (Base58Check-encoded)", + "$ref": "#/definitions/unistring" + }, "Context_hash": { "title": "A hash of context (Base58Check-encoded)", "$ref": "#/definitions/unistring" @@ -597,6 +601,10 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "title": "A Tezos protocol ID (Base58Check-encoded)", "$ref": "#/definitions/unistring" }, + "Rejection_hash": { + "title": "A rejection ID (Base58Check-encoded)", + "$ref": "#/definitions/unistring" + }, "Signature": { "title": "A Ed25519, Secp256k1 or P256 signature (Base58Check-encoded)", "$ref": "#/definitions/unistring" @@ -609,6 +617,10 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "title": "A Ed25519, Secp256k1, or P256 public key hash (Base58Check-encoded)", "$ref": "#/definitions/unistring" }, + "Tx_rollup_l2_address": { + "title": "The hash of a BLS public key used to identify a L2 ticket holders (Base58Check-encoded)", + "$ref": "#/definitions/unistring" + }, "alpha.block_header.alpha.full_header": { "title": "Shell header", "description": "Block header's shell-related content. It contains information such as the block level, its predecessor and timestamp.", @@ -683,6 +695,11 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' ], "additionalProperties": false }, + "alpha.contract_id": { + "title": "A contract handle", + "description": "A contract notation as given to an RPC or inside scripts. Can be a base58 implicit contract hash or a base58 originated contract hash.", + "$ref": "#/definitions/unistring" + }, "alpha.entrypoint": { "title": "entrypoint", "description": "Named entrypoint to a Michelson smart contract", @@ -862,14 +879,14 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "False", "DUG", "DIG", - "chest_key", + "ticket", "BLAKE2B", "list", - "bls12_381_g1", + "never", "Pair", "INT", "nat", - "never", + "chain_id", "storage", "SIZE", "view", @@ -886,15 +903,15 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "operation", "MAP", "option", - "bls12_381_fr", + "bls12_381_g2", "ADD", "IMPLICIT_ACCOUNT", "SHA512", "int", "LSL", - "bls12_381_g2", - "ticket", - "sapling_transaction", + "bls12_381_g1", + "bls12_381_fr", + "tx_rollup_l2_address", "COMPARE", "SWAP", "STEPS_TO_QUOTA", @@ -902,6 +919,7 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "pair", "BALANCE", "CONCAT", + "constant", "MUL", "FAILWITH", "Elt", @@ -960,7 +978,7 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "PACK", "IF_CONS", "KECCAK", - "chest", + "chest_key", "UNIT", "EMPTY_SET", "NEQ", @@ -972,7 +990,7 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "contract", "LSR", "EMPTY_BIG_MAP", - "sapling_state", + "sapling_transaction", "JOIN_TICKETS", "LEVEL", "UNPAIR", @@ -980,8 +998,8 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "PUSH", "big_map", "GT", - "chain_id", - "constant", + "sapling_state", + "chest", "NOW", "IF_NONE", "PAIR", @@ -1797,6 +1815,314 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' ], "additionalProperties": false }, + { + "title": "Tx_rollup_commit", + "type": "object", + "properties": { + "kind": { + "type": "string", + "enum": [ + "tx_rollup_commit" + ] + }, + "source": { + "$ref": "#/definitions/Signature.Public_key_hash" + }, + "fee": { + "$ref": "#/definitions/alpha.mutez" + }, + "counter": { + "$ref": "#/definitions/positive_bignum" + }, + "gas_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "storage_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "rollup": { + "$ref": "#/definitions/alpha.tx_rollup_id" + }, + "commitment": { + "type": "object", + "properties": { + "level": { + "type": "integer", + "minimum": -2147483648, + "maximum": 2147483647 + }, + "batches": { + "type": "array", + "items": { + "type": "object", + "properties": { + "effects": { + "type": "array", + "items": { + "type": "object", + "properties": { + "contract": { + "$ref": "#/definitions/alpha.contract_id" + }, + "ticket": { + "$ref": "#/definitions/script_expr" + }, + "amount": { + "$ref": "#/definitions/int64" + } + }, + "required": [ + "amount", + "ticket", + "contract" + ], + "additionalProperties": false + } + }, + "root": { + "type": "string", + "pattern": "^([a-zA-Z0-9][a-zA-Z0-9])*$" + } + }, + "required": [ + "root", + "effects" + ], + "additionalProperties": false + } + }, + "predecessor": { + "oneOf": [ + { + "title": "Some", + "$ref": "#/definitions/Commitment_hash" + }, + { + "title": "None", + "type": "null" + } + ] + } + }, + "required": [ + "predecessor", + "batches", + "level" + ], + "additionalProperties": false + } + }, + "required": [ + "commitment", + "rollup", + "storage_limit", + "gas_limit", + "counter", + "fee", + "source", + "kind" + ], + "additionalProperties": false + }, + { + "title": "Tx_rollup_return_bond", + "type": "object", + "properties": { + "kind": { + "type": "string", + "enum": [ + "tx_rollup_return_bond" + ] + }, + "source": { + "$ref": "#/definitions/Signature.Public_key_hash" + }, + "fee": { + "$ref": "#/definitions/alpha.mutez" + }, + "counter": { + "$ref": "#/definitions/positive_bignum" + }, + "gas_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "storage_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "rollup": { + "$ref": "#/definitions/alpha.tx_rollup_id" + } + }, + "required": [ + "rollup", + "storage_limit", + "gas_limit", + "counter", + "fee", + "source", + "kind" + ], + "additionalProperties": false + }, + { + "title": "Tx_rollup_rejection", + "type": "object", + "properties": { + "kind": { + "type": "string", + "enum": [ + "tx_rollup_rejection" + ] + }, + "source": { + "$ref": "#/definitions/Signature.Public_key_hash" + }, + "fee": { + "$ref": "#/definitions/alpha.mutez" + }, + "counter": { + "$ref": "#/definitions/positive_bignum" + }, + "gas_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "storage_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "rollup": { + "$ref": "#/definitions/alpha.tx_rollup_id" + }, + "level": { + "type": "integer", + "minimum": -2147483648, + "maximum": 2147483647 + }, + "hash": { + "$ref": "#/definitions/Commitment_hash" + }, + "batch_index": { + "type": "integer", + "minimum": -1073741824, + "maximum": 1073741823 + }, + "batch": { + "oneOf": [ + { + "title": "Batch", + "type": "object", + "properties": { + "batch": { + "$ref": "#/definitions/unistring" + } + }, + "required": [ + "batch" + ], + "additionalProperties": false + }, + { + "title": "Deposit", + "type": "object", + "properties": { + "deposit": { + "type": "object", + "properties": { + "destination": { + "oneOf": [ + { + "title": "Key", + "type": "integer", + "minimum": -2147483648, + "maximum": 2147483647 + }, + { + "title": "Value", + "$ref": "#/definitions/Tx_rollup_l2_address" + } + ] + }, + "ticket_hash": { + "$ref": "#/definitions/script_expr" + }, + "amount": { + "$ref": "#/definitions/int64" + } + }, + "required": [ + "amount", + "ticket_hash", + "destination" + ], + "additionalProperties": false + } + }, + "required": [ + "deposit" + ], + "additionalProperties": false + } + ] + }, + "nonce": { + "$ref": "#/definitions/int64" + } + }, + "required": [ + "nonce", + "batch", + "batch_index", + "hash", + "level", + "rollup", + "storage_limit", + "gas_limit", + "counter", + "fee", + "source", + "kind" + ], + "additionalProperties": false + }, + { + "title": "Tx_rollup_prerejection", + "type": "object", + "properties": { + "kind": { + "type": "string", + "enum": [ + "tx_rollup_prerejection" + ] + }, + "source": { + "$ref": "#/definitions/Signature.Public_key_hash" + }, + "fee": { + "$ref": "#/definitions/alpha.mutez" + }, + "counter": { + "$ref": "#/definitions/positive_bignum" + }, + "gas_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "storage_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "hash": { + "$ref": "#/definitions/Rejection_hash" + } + }, + "required": [ + "hash", + "storage_limit", + "gas_limit", + "counter", + "fee", + "source", + "kind" + ], + "additionalProperties": false + }, { "title": "Sc_rollup_originate", "type": "object", @@ -2065,7 +2391,7 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' }, "alpha.transaction_destination": { "title": "A destination of a transaction", - "description": "A destination notation compatible with the contract notation as given to an RPC or inside scripts. Can be a base58 implicit contract hash or a base58 originated contract hash.", + "description": "A destination notation compatible with the contract notation as given to an RPC or inside scripts. Can be a base58 implicit contract hash, a base58 originated contract hash, or a base58 originated transaction rollup.", "$ref": "#/definitions/unistring" }, "alpha.tx_rollup_id": { @@ -2098,6 +2424,11 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "pattern": "^([a-zA-Z0-9][a-zA-Z0-9])*$" } }, + "int64": { + "title": "64 bit integers", + "description": "Decimal representation of 64 bit integers", + "type": "string" + }, "micheline.alpha.michelson_v1.expression": { "oneOf": [ { @@ -2180,6 +2511,10 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "description": "Decimal representation of a positive big number", "type": "string" }, + "script_expr": { + "title": "A script expression ID (Base58Check-encoded)", + "$ref": "#/definitions/unistring" + }, "timestamp.protocol": { "description": "A timestamp as seen by the protocol: second-level precision, epoch based.", "$ref": "#/definitions/unistring" @@ -2307,54 +2642,14 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' }, { "description": { - "title": "alpha.scripted.contracts" + "title": "X_4" }, "encoding": { - "fields": [ - { - "kind": "dyn", - "num_fields": 1, - "size": "Uint30" - }, - { - "name": "code", - "layout": { - "kind": "Bytes" - }, - "data_kind": { - "kind": "Variable" - }, - "kind": "named" - }, - { - "kind": "dyn", - "num_fields": 1, - "size": "Uint30" - }, - { - "name": "storage", - "layout": { - "kind": "Bytes" - }, - "data_kind": { - "kind": "Variable" - }, - "kind": "named" - } - ] - } - }, - { - "description": { - "title": "alpha.transaction_destination" - }, - "encoding": { - "tag_size": "Uint8", - "kind": { - "size": 22, - "kind": "Float" - }, - "cases": [ + "tag_size": "Uint8", + "kind": { + "kind": "Dynamic" + }, + "cases": [ { "tag": 0, "fields": [ @@ -2371,19 +2666,18 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "Signature.Public_key_hash", "layout": { - "name": "public_key_hash", - "kind": "Ref" + "size": "Int32", + "kind": "Int" }, + "kind": "anon", "data_kind": { - "size": 21, + "size": 4, "kind": "Float" - }, - "kind": "named" + } } ], - "name": "Implicit" + "name": "Key" }, { "tag": 1, @@ -2401,7 +2695,7 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "Contract_hash", + "name": "Tx_rollup_l2_address", "layout": { "kind": "Bytes" }, @@ -2410,27 +2704,59 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "Float" }, "kind": "named" - }, - { - "name": "padding", - "layout": { - "kind": "Padding" - }, - "data_kind": { - "size": 1, - "kind": "Float" - }, - "kind": "named" } ], - "name": "Originated" + "name": "Value" } ] } }, { "description": { - "title": "alpha.entrypoint" + "title": "X_3" + }, + "encoding": { + "fields": [ + { + "name": "destination", + "layout": { + "name": "X_4", + "kind": "Ref" + }, + "data_kind": { + "kind": "Dynamic" + }, + "kind": "named" + }, + { + "name": "ticket_hash", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 32, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "amount", + "layout": { + "size": "Int64", + "kind": "Int" + }, + "data_kind": { + "size": 8, + "kind": "Float" + }, + "kind": "named" + } + ] + } + }, + { + "description": { + "title": "X_5" }, "encoding": { "tag_size": "Uint8", @@ -2454,17 +2780,22 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "batch", "layout": { - "kind": "Zero_width" + "kind": "String" }, - "kind": "anon", "data_kind": { - "size": 0, - "kind": "Float" - } + "kind": "Variable" + }, + "kind": "named" } ], - "name": "default" + "name": "Batch" }, { "tag": 1, @@ -2482,20 +2813,35 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { + "name": "deposit", "layout": { - "kind": "Zero_width" + "name": "X_3", + "kind": "Ref" }, - "kind": "anon", "data_kind": { - "size": 0, - "kind": "Float" - } + "kind": "Dynamic" + }, + "kind": "named" } ], - "name": "root" - }, + "name": "Deposit" + } + ] + } + }, + { + "description": { + "title": "alpha.contract_id" + }, + "encoding": { + "tag_size": "Uint8", + "kind": { + "size": 22, + "kind": "Float" + }, + "cases": [ { - "tag": 2, + "tag": 0, "fields": [ { "name": "Tag", @@ -2510,20 +2856,22 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { + "name": "Signature.Public_key_hash", "layout": { - "kind": "Zero_width" + "name": "public_key_hash", + "kind": "Ref" }, - "kind": "anon", "data_kind": { - "size": 0, + "size": 21, "kind": "Float" - } + }, + "kind": "named" } ], - "name": "do" + "name": "Implicit" }, { - "tag": 3, + "tag": 1, "fields": [ { "name": "Tag", @@ -2538,110 +2886,71 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { + "name": "Contract_hash", "layout": { - "kind": "Zero_width" - }, - "kind": "anon", - "data_kind": { - "size": 0, - "kind": "Float" - } - } - ], - "name": "set_delegate" - }, - { - "tag": 4, - "fields": [ - { - "name": "Tag", - "layout": { - "size": "Uint8", - "kind": "Int" + "kind": "Bytes" }, "data_kind": { - "size": 1, + "size": 20, "kind": "Float" }, "kind": "named" }, { + "name": "padding", "layout": { - "kind": "Zero_width" - }, - "kind": "anon", - "data_kind": { - "size": 0, - "kind": "Float" - } - } - ], - "name": "remove_delegate" - }, - { - "tag": 255, - "fields": [ - { - "name": "Tag", - "layout": { - "size": "Uint8", - "kind": "Int" + "kind": "Padding" }, "data_kind": { "size": 1, "kind": "Float" }, "kind": "named" - }, - { - "kind": "dyn", - "num_fields": 1, - "size": "Uint8" - }, - { - "layout": { - "kind": "String" - }, - "kind": "anon", - "data_kind": { - "kind": "Variable" - } } ], - "name": "named" + "name": "Originated" } ] } }, { "description": { - "title": "X_3" + "title": "X_8" }, "encoding": { "fields": [ { - "name": "entrypoint", + "name": "contract", "layout": { - "name": "alpha.entrypoint", + "name": "alpha.contract_id", "kind": "Ref" }, "data_kind": { - "kind": "Dynamic" + "size": 22, + "kind": "Float" }, "kind": "named" }, { - "kind": "dyn", - "num_fields": 1, - "size": "Uint30" + "name": "ticket", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 32, + "kind": "Float" + }, + "kind": "named" }, { - "name": "value", + "name": "amount", "layout": { - "kind": "Bytes" + "size": "Int64", + "kind": "Int" }, "data_kind": { - "kind": "Variable" + "size": 8, + "kind": "Float" }, "kind": "named" } @@ -2650,18 +2959,41 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' }, { "description": { - "title": "N.t", - "description": "A variable-length sequence of bytes encoding a Zarith natural number. Each byte has a running unary size bit: the most significant bit of each byte indicates whether this is the last byte in the sequence (0) or whether the sequence continues (1). Size bits ignored, the data is the binary representation of the number in little-endian order." + "title": "X_7" }, "encoding": { "fields": [ { - "name": "N.t", - "layout": { - "kind": "Bytes" - }, - "data_kind": { - "kind": "Dynamic" + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "effects", + "layout": { + "layout": { + "name": "X_8", + "kind": "Ref" + }, + "kind": "Seq" + }, + "data_kind": { + "kind": "Variable" + }, + "kind": "named" + }, + { + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "root", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "kind": "Variable" }, "kind": "named" } @@ -2670,7 +3002,7 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' }, { "description": { - "title": "public_key" + "title": "X_9" }, "encoding": { "tag_size": "Uint8", @@ -2694,18 +3026,17 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "Ed25519.Public_key", "layout": { - "kind": "Bytes" + "kind": "Zero_width" }, + "kind": "anon", "data_kind": { - "size": 32, + "size": 0, "kind": "Float" - }, - "kind": "named" + } } ], - "name": "Ed25519" + "name": "None" }, { "tag": 1, @@ -2723,161 +3054,101 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "Secp256k1.Public_key", - "layout": { - "kind": "Bytes" - }, - "data_kind": { - "size": 33, - "kind": "Float" - }, - "kind": "named" - } - ], - "name": "Secp256k1" - }, - { - "tag": 2, - "fields": [ - { - "name": "Tag", - "layout": { - "size": "Uint8", - "kind": "Int" - }, - "data_kind": { - "size": 1, - "kind": "Float" - }, - "kind": "named" - }, - { - "name": "P256.Public_key", + "name": "Commitment_hash", "layout": { "kind": "Bytes" }, "data_kind": { - "size": 33, + "size": 32, "kind": "Float" }, "kind": "named" } ], - "name": "P256" + "name": "Some" } ] } }, { "description": { - "title": "alpha.inlined.preendorsement.contents" + "title": "X_6" }, "encoding": { - "tag_size": "Uint8", - "kind": { - "size": 43, - "kind": "Float" - }, - "cases": [ + "fields": [ { - "tag": 20, - "fields": [ - { - "name": "Tag", - "layout": { - "size": "Uint8", - "kind": "Int" - }, - "data_kind": { - "size": 1, - "kind": "Float" - }, - "kind": "named" - }, - { - "name": "slot", - "layout": { - "size": "Uint16", - "kind": "Int" - }, - "data_kind": { - "size": 2, - "kind": "Float" - }, - "kind": "named" - }, - { - "name": "level", - "layout": { - "size": "Int32", - "kind": "Int" - }, - "data_kind": { - "size": 4, - "kind": "Float" - }, - "kind": "named" - }, - { - "name": "round", - "layout": { - "size": "Int32", - "kind": "Int" - }, - "data_kind": { - "size": 4, - "kind": "Float" - }, - "kind": "named" + "name": "level", + "layout": { + "size": "Int32", + "kind": "Int" + }, + "data_kind": { + "size": 4, + "kind": "Float" + }, + "kind": "named" + }, + { + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "batches", + "layout": { + "layout": { + "name": "X_7", + "kind": "Ref" }, - { - "name": "block_payload_hash", - "layout": { - "kind": "Bytes" - }, - "data_kind": { - "size": 32, - "kind": "Float" - }, - "kind": "named" - } - ], - "name": "Preendorsement" + "kind": "Seq" + }, + "data_kind": { + "kind": "Variable" + }, + "kind": "named" + }, + { + "name": "predecessor", + "layout": { + "name": "X_9", + "kind": "Ref" + }, + "data_kind": { + "kind": "Dynamic" + }, + "kind": "named" } ] } }, { "description": { - "title": "alpha.inlined.preendorsement" + "title": "alpha.scripted.contracts" }, "encoding": { "fields": [ { - "name": "branch", + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "code", "layout": { "kind": "Bytes" }, "data_kind": { - "size": 32, - "kind": "Float" + "kind": "Variable" }, "kind": "named" }, { - "name": "operations", - "layout": { - "name": "alpha.inlined.preendorsement.contents", - "kind": "Ref" - }, - "data_kind": { - "size": 43, - "kind": "Float" - }, - "kind": "named" + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" }, { - "name": "signature", + "name": "storage", "layout": { "kind": "Bytes" }, @@ -2891,12 +3162,12 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' }, { "description": { - "title": "public_key_hash" + "title": "alpha.transaction_destination" }, "encoding": { "tag_size": "Uint8", "kind": { - "size": 21, + "size": 22, "kind": "Float" }, "cases": [ @@ -2916,18 +3187,19 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "Ed25519.Public_key_hash", + "name": "Signature.Public_key_hash", "layout": { - "kind": "Bytes" + "name": "public_key_hash", + "kind": "Ref" }, "data_kind": { - "size": 20, + "size": 21, "kind": "Float" }, "kind": "named" } ], - "name": "Ed25519" + "name": "Implicit" }, { "tag": 1, @@ -2945,7 +3217,7 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "Secp256k1.Public_key_hash", + "name": "Contract_hash", "layout": { "kind": "Bytes" }, @@ -2954,9 +3226,20 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "Float" }, "kind": "named" + }, + { + "name": "padding", + "layout": { + "kind": "Padding" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" } ], - "name": "Secp256k1" + "name": "Originated" }, { "tag": 2, @@ -2974,7 +3257,7 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "P256.Public_key_hash", + "name": "Rollup_hash", "layout": { "kind": "Bytes" }, @@ -2983,145 +3266,451 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "Float" }, "kind": "named" + }, + { + "name": "padding", + "layout": { + "kind": "Padding" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" } ], - "name": "P256" + "name": "Tx_rollup" } ] } }, { "description": { - "title": "fitness.elem" + "title": "alpha.entrypoint" }, "encoding": { - "fields": [ + "tag_size": "Uint8", + "kind": { + "kind": "Dynamic" + }, + "cases": [ { - "kind": "dyn", - "num_fields": 1, - "size": "Uint30" + "tag": 0, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "layout": { + "kind": "Zero_width" + }, + "kind": "anon", + "data_kind": { + "size": 0, + "kind": "Float" + } + } + ], + "name": "default" }, { - "layout": { - "kind": "Bytes" - }, - "kind": "anon", - "data_kind": { - "kind": "Variable" - } + "tag": 1, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "layout": { + "kind": "Zero_width" + }, + "kind": "anon", + "data_kind": { + "size": 0, + "kind": "Float" + } + } + ], + "name": "root" + }, + { + "tag": 2, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "layout": { + "kind": "Zero_width" + }, + "kind": "anon", + "data_kind": { + "size": 0, + "kind": "Float" + } + } + ], + "name": "do" + }, + { + "tag": 3, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "layout": { + "kind": "Zero_width" + }, + "kind": "anon", + "data_kind": { + "size": 0, + "kind": "Float" + } + } + ], + "name": "set_delegate" + }, + { + "tag": 4, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "layout": { + "kind": "Zero_width" + }, + "kind": "anon", + "data_kind": { + "size": 0, + "kind": "Float" + } + } + ], + "name": "remove_delegate" + }, + { + "tag": 255, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "kind": "dyn", + "num_fields": 1, + "size": "Uint8" + }, + { + "layout": { + "kind": "String" + }, + "kind": "anon", + "data_kind": { + "kind": "Variable" + } + } + ], + "name": "named" } ] } }, { "description": { - "title": "alpha.block_header.alpha.full_header" + "title": "X_10" }, "encoding": { "fields": [ { - "name": "level", + "name": "entrypoint", "layout": { - "size": "Int32", - "kind": "Int" + "name": "alpha.entrypoint", + "kind": "Ref" }, "data_kind": { - "size": 4, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" }, { - "name": "proto", - "layout": { - "size": "Uint8", - "kind": "Int" - }, - "data_kind": { - "size": 1, - "kind": "Float" - }, - "kind": "named" + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" }, { - "name": "predecessor", + "name": "value", "layout": { "kind": "Bytes" }, "data_kind": { - "size": 32, - "kind": "Float" - }, - "kind": "named" - }, - { - "name": "timestamp", - "layout": { - "size": "Int64", - "kind": "Int" - }, - "data_kind": { - "size": 8, - "kind": "Float" - }, - "kind": "named" - }, - { - "name": "validation_pass", - "layout": { - "size": "Uint8", - "kind": "Int" - }, - "data_kind": { - "size": 1, - "kind": "Float" + "kind": "Variable" }, "kind": "named" - }, + } + ] + } + }, + { + "description": { + "title": "N.t", + "description": "A variable-length sequence of bytes encoding a Zarith natural number. Each byte has a running unary size bit: the most significant bit of each byte indicates whether this is the last byte in the sequence (0) or whether the sequence continues (1). Size bits ignored, the data is the binary representation of the number in little-endian order." + }, + "encoding": { + "fields": [ { - "name": "operations_hash", + "name": "N.t", "layout": { "kind": "Bytes" }, "data_kind": { - "size": 32, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" - }, - { - "kind": "dyn", - "name": "fitness", - "num_fields": 1, - "size": "Uint30" - }, - { - "name": "fitness", - "layout": { - "layout": { - "name": "fitness.elem", - "kind": "Ref" + } + ] + } + }, + { + "description": { + "title": "public_key" + }, + "encoding": { + "tag_size": "Uint8", + "kind": { + "kind": "Dynamic" + }, + "cases": [ + { + "tag": 0, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" }, - "kind": "Seq" - }, - "data_kind": { - "kind": "Variable" - }, - "kind": "named" + { + "name": "Ed25519.Public_key", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 32, + "kind": "Float" + }, + "kind": "named" + } + ], + "name": "Ed25519" }, { - "name": "context", - "layout": { - "kind": "Bytes" - }, - "data_kind": { - "size": 32, - "kind": "Float" - }, - "kind": "named" + "tag": 1, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "Secp256k1.Public_key", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 33, + "kind": "Float" + }, + "kind": "named" + } + ], + "name": "Secp256k1" }, { - "name": "payload_hash", + "tag": 2, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "P256.Public_key", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 33, + "kind": "Float" + }, + "kind": "named" + } + ], + "name": "P256" + } + ] + } + }, + { + "description": { + "title": "alpha.inlined.preendorsement.contents" + }, + "encoding": { + "tag_size": "Uint8", + "kind": { + "size": 43, + "kind": "Float" + }, + "cases": [ + { + "tag": 20, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "slot", + "layout": { + "size": "Uint16", + "kind": "Int" + }, + "data_kind": { + "size": 2, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "level", + "layout": { + "size": "Int32", + "kind": "Int" + }, + "data_kind": { + "size": 4, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "round", + "layout": { + "size": "Int32", + "kind": "Int" + }, + "data_kind": { + "size": 4, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "block_payload_hash", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 32, + "kind": "Float" + }, + "kind": "named" + } + ], + "name": "Preendorsement" + } + ] + } + }, + { + "description": { + "title": "alpha.inlined.preendorsement" + }, + "encoding": { + "fields": [ + { + "name": "branch", "layout": { "kind": "Bytes" }, @@ -3132,81 +3721,774 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "payload_round", - "layout": { - "size": "Int32", - "kind": "Int" - }, - "data_kind": { - "size": 4, - "kind": "Float" - }, - "kind": "named" - }, - { - "name": "proof_of_work_nonce", + "name": "operations", "layout": { - "kind": "Bytes" + "name": "alpha.inlined.preendorsement.contents", + "kind": "Ref" }, "data_kind": { - "size": 8, + "size": 43, "kind": "Float" }, "kind": "named" }, { - "kind": "option_indicator", - "name": "seed_nonce_hash" - }, - { - "name": "seed_nonce_hash", + "name": "signature", "layout": { "kind": "Bytes" }, "data_kind": { - "size": 32, - "kind": "Float" + "kind": "Variable" }, "kind": "named" - }, + } + ] + } + }, + { + "description": { + "title": "public_key_hash" + }, + "encoding": { + "tag_size": "Uint8", + "kind": { + "size": 21, + "kind": "Float" + }, + "cases": [ { - "name": "liquidity_baking_escape_vote", - "layout": { - "kind": "Bool" - }, - "data_kind": { - "size": 1, - "kind": "Float" - }, + "tag": 0, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "Ed25519.Public_key_hash", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 20, + "kind": "Float" + }, + "kind": "named" + } + ], + "name": "Ed25519" + }, + { + "tag": 1, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "Secp256k1.Public_key_hash", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 20, + "kind": "Float" + }, + "kind": "named" + } + ], + "name": "Secp256k1" + }, + { + "tag": 2, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "P256.Public_key_hash", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 20, + "kind": "Float" + }, + "kind": "named" + } + ], + "name": "P256" + } + ] + } + }, + { + "description": { + "title": "fitness.elem" + }, + "encoding": { + "fields": [ + { + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "layout": { + "kind": "Bytes" + }, + "kind": "anon", + "data_kind": { + "kind": "Variable" + } + } + ] + } + }, + { + "description": { + "title": "alpha.block_header.alpha.full_header" + }, + "encoding": { + "fields": [ + { + "name": "level", + "layout": { + "size": "Int32", + "kind": "Int" + }, + "data_kind": { + "size": 4, + "kind": "Float" + }, "kind": "named" }, { - "name": "signature", - "layout": { - "kind": "Bytes" - }, - "data_kind": { - "size": 64, - "kind": "Float" - }, - "kind": "named" - } - ] - } - }, - { - "description": { - "title": "alpha.inlined.endorsement_mempool.contents" - }, - "encoding": { - "tag_size": "Uint8", - "kind": { - "size": 43, - "kind": "Float" - }, - "cases": [ - { - "tag": 21, + "name": "proto", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "predecessor", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 32, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "timestamp", + "layout": { + "size": "Int64", + "kind": "Int" + }, + "data_kind": { + "size": 8, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "validation_pass", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "operations_hash", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 32, + "kind": "Float" + }, + "kind": "named" + }, + { + "kind": "dyn", + "name": "fitness", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "fitness", + "layout": { + "layout": { + "name": "fitness.elem", + "kind": "Ref" + }, + "kind": "Seq" + }, + "data_kind": { + "kind": "Variable" + }, + "kind": "named" + }, + { + "name": "context", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 32, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "payload_hash", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 32, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "payload_round", + "layout": { + "size": "Int32", + "kind": "Int" + }, + "data_kind": { + "size": 4, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "proof_of_work_nonce", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 8, + "kind": "Float" + }, + "kind": "named" + }, + { + "kind": "option_indicator", + "name": "seed_nonce_hash" + }, + { + "name": "seed_nonce_hash", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 32, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "liquidity_baking_escape_vote", + "layout": { + "kind": "Bool" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "signature", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 64, + "kind": "Float" + }, + "kind": "named" + } + ] + } + }, + { + "description": { + "title": "alpha.inlined.endorsement_mempool.contents" + }, + "encoding": { + "tag_size": "Uint8", + "kind": { + "size": 43, + "kind": "Float" + }, + "cases": [ + { + "tag": 21, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "slot", + "layout": { + "size": "Uint16", + "kind": "Int" + }, + "data_kind": { + "size": 2, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "level", + "layout": { + "size": "Int32", + "kind": "Int" + }, + "data_kind": { + "size": 4, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "round", + "layout": { + "size": "Int32", + "kind": "Int" + }, + "data_kind": { + "size": 4, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "block_payload_hash", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 32, + "kind": "Float" + }, + "kind": "named" + } + ], + "name": "Endorsement" + } + ] + } + }, + { + "description": { + "title": "alpha.inlined.endorsement" + }, + "encoding": { + "fields": [ + { + "name": "branch", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 32, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "operations", + "layout": { + "name": "alpha.inlined.endorsement_mempool.contents", + "kind": "Ref" + }, + "data_kind": { + "size": 43, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "signature", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "kind": "Variable" + }, + "kind": "named" + } + ] + } + }, + { + "description": { + "title": "alpha.operation.alpha.contents" + }, + "encoding": { + "tag_size": "Uint8", + "kind": { + "kind": "Dynamic" + }, + "cases": [ + { + "tag": 1, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "level", + "layout": { + "size": "Int32", + "kind": "Int" + }, + "data_kind": { + "size": 4, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "nonce", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 32, + "kind": "Float" + }, + "kind": "named" + } + ], + "name": "Seed_nonce_revelation" + }, + { + "tag": 2, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "op1", + "layout": { + "name": "alpha.inlined.endorsement", + "kind": "Ref" + }, + "data_kind": { + "kind": "Variable" + }, + "kind": "named" + }, + { + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "op2", + "layout": { + "name": "alpha.inlined.endorsement", + "kind": "Ref" + }, + "data_kind": { + "kind": "Variable" + }, + "kind": "named" + } + ], + "name": "Double_endorsement_evidence" + }, + { + "tag": 3, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "bh1", + "layout": { + "name": "alpha.block_header.alpha.full_header", + "kind": "Ref" + }, + "data_kind": { + "kind": "Dynamic" + }, + "kind": "named" + }, + { + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "bh2", + "layout": { + "name": "alpha.block_header.alpha.full_header", + "kind": "Ref" + }, + "data_kind": { + "kind": "Dynamic" + }, + "kind": "named" + } + ], + "name": "Double_baking_evidence" + }, + { + "tag": 4, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "pkh", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 20, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "secret", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 20, + "kind": "Float" + }, + "kind": "named" + } + ], + "name": "Activate_account" + }, + { + "tag": 5, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "source", + "layout": { + "name": "public_key_hash", + "kind": "Ref" + }, + "data_kind": { + "size": 21, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "period", + "layout": { + "size": "Int32", + "kind": "Int" + }, + "data_kind": { + "size": 4, + "kind": "Float" + }, + "kind": "named" + }, + { + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "proposals", + "layout": { + "layout": { + "kind": "Bytes" + }, + "kind": "Seq" + }, + "data_kind": { + "kind": "Variable" + }, + "kind": "named" + } + ], + "name": "Proposals" + }, + { + "tag": 6, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "source", + "layout": { + "name": "public_key_hash", + "kind": "Ref" + }, + "data_kind": { + "size": 21, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "period", + "layout": { + "size": "Int32", + "kind": "Int" + }, + "data_kind": { + "size": 4, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "proposal", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 32, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "ballot", + "layout": { + "size": "Int8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + } + ], + "name": "Ballot" + }, + { + "tag": 7, "fields": [ { "name": "Tag", @@ -3221,112 +4503,75 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "slot", + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "op1", "layout": { - "size": "Uint16", - "kind": "Int" + "name": "alpha.inlined.preendorsement", + "kind": "Ref" }, "data_kind": { - "size": 2, - "kind": "Float" + "kind": "Variable" }, "kind": "named" }, { - "name": "level", + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "op2", "layout": { - "size": "Int32", - "kind": "Int" + "name": "alpha.inlined.preendorsement", + "kind": "Ref" }, "data_kind": { - "size": 4, - "kind": "Float" + "kind": "Variable" }, "kind": "named" - }, + } + ], + "name": "Double_preendorsement_evidence" + }, + { + "tag": 17, + "fields": [ { - "name": "round", + "name": "Tag", "layout": { - "size": "Int32", + "size": "Uint8", "kind": "Int" }, "data_kind": { - "size": 4, + "size": 1, "kind": "Float" }, "kind": "named" }, { - "name": "block_payload_hash", + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "arbitrary", "layout": { - "kind": "Bytes" + "kind": "String" }, "data_kind": { - "size": 32, - "kind": "Float" + "kind": "Variable" }, "kind": "named" } ], - "name": "Endorsement" - } - ] - } - }, - { - "description": { - "title": "alpha.inlined.endorsement" - }, - "encoding": { - "fields": [ - { - "name": "branch", - "layout": { - "kind": "Bytes" - }, - "data_kind": { - "size": 32, - "kind": "Float" - }, - "kind": "named" - }, - { - "name": "operations", - "layout": { - "name": "alpha.inlined.endorsement_mempool.contents", - "kind": "Ref" - }, - "data_kind": { - "size": 43, - "kind": "Float" - }, - "kind": "named" + "name": "Failing_noop" }, { - "name": "signature", - "layout": { - "kind": "Bytes" - }, - "data_kind": { - "kind": "Variable" - }, - "kind": "named" - } - ] - } - }, - { - "description": { - "title": "alpha.operation.alpha.contents" - }, - "encoding": { - "tag_size": "Uint8", - "kind": { - "kind": "Dynamic" - }, - "cases": [ - { - "tag": 1, + "tag": 20, "fields": [ { "name": "Tag", @@ -3340,6 +4585,18 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' }, "kind": "named" }, + { + "name": "slot", + "layout": { + "size": "Uint16", + "kind": "Int" + }, + "data_kind": { + "size": 2, + "kind": "Float" + }, + "kind": "named" + }, { "name": "level", "layout": { @@ -3353,7 +4610,19 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "nonce", + "name": "round", + "layout": { + "size": "Int32", + "kind": "Int" + }, + "data_kind": { + "size": 4, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "block_payload_hash", "layout": { "kind": "Bytes" }, @@ -3364,10 +4633,10 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" } ], - "name": "Seed_nonce_revelation" + "name": "Preendorsement" }, { - "tag": 2, + "tag": 21, "fields": [ { "name": "Tag", @@ -3382,42 +4651,57 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "kind": "dyn", - "num_fields": 1, - "size": "Uint30" + "name": "slot", + "layout": { + "size": "Uint16", + "kind": "Int" + }, + "data_kind": { + "size": 2, + "kind": "Float" + }, + "kind": "named" }, { - "name": "op1", + "name": "level", "layout": { - "name": "alpha.inlined.endorsement", - "kind": "Ref" + "size": "Int32", + "kind": "Int" }, "data_kind": { - "kind": "Variable" + "size": 4, + "kind": "Float" }, "kind": "named" }, { - "kind": "dyn", - "num_fields": 1, - "size": "Uint30" + "name": "round", + "layout": { + "size": "Int32", + "kind": "Int" + }, + "data_kind": { + "size": 4, + "kind": "Float" + }, + "kind": "named" }, { - "name": "op2", + "name": "block_payload_hash", "layout": { - "name": "alpha.inlined.endorsement", - "kind": "Ref" + "kind": "Bytes" }, "data_kind": { - "kind": "Variable" + "size": 32, + "kind": "Float" }, "kind": "named" } ], - "name": "Double_endorsement_evidence" + "name": "Endorsement" }, { - "tag": 3, + "tag": 107, "fields": [ { "name": "Tag", @@ -3432,14 +4716,21 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "kind": "dyn", - "num_fields": 1, - "size": "Uint30" + "name": "source", + "layout": { + "name": "public_key_hash", + "kind": "Ref" + }, + "data_kind": { + "size": 21, + "kind": "Float" + }, + "kind": "named" }, { - "name": "bh1", + "name": "fee", "layout": { - "name": "alpha.block_header.alpha.full_header", + "name": "N.t", "kind": "Ref" }, "data_kind": { @@ -3448,66 +4739,54 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "kind": "dyn", - "num_fields": 1, - "size": "Uint30" - }, - { - "name": "bh2", + "name": "counter", "layout": { - "name": "alpha.block_header.alpha.full_header", + "name": "N.t", "kind": "Ref" }, "data_kind": { "kind": "Dynamic" }, - "kind": "named" - } - ], - "name": "Double_baking_evidence" - }, - { - "tag": 4, - "fields": [ + "kind": "named" + }, { - "name": "Tag", + "name": "gas_limit", "layout": { - "size": "Uint8", - "kind": "Int" + "name": "N.t", + "kind": "Ref" }, "data_kind": { - "size": 1, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" }, { - "name": "pkh", + "name": "storage_limit", "layout": { - "kind": "Bytes" + "name": "N.t", + "kind": "Ref" }, "data_kind": { - "size": 20, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" }, { - "name": "secret", + "name": "public_key", "layout": { - "kind": "Bytes" + "name": "public_key", + "kind": "Ref" }, "data_kind": { - "size": 20, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" } ], - "name": "Activate_account" + "name": "Reveal" }, { - "tag": 5, + "tag": 108, "fields": [ { "name": "Tag", @@ -3534,105 +4813,92 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "period", + "name": "fee", "layout": { - "size": "Int32", - "kind": "Int" + "name": "N.t", + "kind": "Ref" }, "data_kind": { - "size": 4, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" }, { - "kind": "dyn", - "num_fields": 1, - "size": "Uint30" - }, - { - "name": "proposals", + "name": "counter", "layout": { - "layout": { - "kind": "Bytes" - }, - "kind": "Seq" + "name": "N.t", + "kind": "Ref" }, "data_kind": { - "kind": "Variable" + "kind": "Dynamic" }, "kind": "named" - } - ], - "name": "Proposals" - }, - { - "tag": 6, - "fields": [ + }, { - "name": "Tag", + "name": "gas_limit", "layout": { - "size": "Uint8", - "kind": "Int" + "name": "N.t", + "kind": "Ref" }, "data_kind": { - "size": 1, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" }, { - "name": "source", + "name": "storage_limit", "layout": { - "name": "public_key_hash", + "name": "N.t", "kind": "Ref" }, "data_kind": { - "size": 21, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" }, { - "name": "period", + "name": "amount", "layout": { - "size": "Int32", - "kind": "Int" + "name": "N.t", + "kind": "Ref" }, "data_kind": { - "size": 4, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" }, { - "name": "proposal", + "name": "destination", "layout": { - "kind": "Bytes" + "name": "alpha.transaction_destination", + "kind": "Ref" }, "data_kind": { - "size": 32, + "size": 22, "kind": "Float" }, "kind": "named" }, { - "name": "ballot", + "kind": "option_indicator", + "name": "parameters" + }, + { + "name": "parameters", "layout": { - "size": "Int8", - "kind": "Int" + "name": "X_10", + "kind": "Ref" }, "data_kind": { - "size": 1, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" } ], - "name": "Ballot" + "name": "Transaction" }, { - "tag": 7, + "tag": 109, "fields": [ { "name": "Tag", @@ -3647,140 +4913,104 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "kind": "dyn", - "num_fields": 1, - "size": "Uint30" - }, - { - "name": "op1", + "name": "source", "layout": { - "name": "alpha.inlined.preendorsement", + "name": "public_key_hash", "kind": "Ref" }, "data_kind": { - "kind": "Variable" + "size": 21, + "kind": "Float" }, "kind": "named" }, { - "kind": "dyn", - "num_fields": 1, - "size": "Uint30" - }, - { - "name": "op2", + "name": "fee", "layout": { - "name": "alpha.inlined.preendorsement", + "name": "N.t", "kind": "Ref" }, "data_kind": { - "kind": "Variable" + "kind": "Dynamic" }, "kind": "named" - } - ], - "name": "Double_preendorsement_evidence" - }, - { - "tag": 17, - "fields": [ + }, { - "name": "Tag", + "name": "counter", "layout": { - "size": "Uint8", - "kind": "Int" + "name": "N.t", + "kind": "Ref" }, "data_kind": { - "size": 1, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" }, { - "kind": "dyn", - "num_fields": 1, - "size": "Uint30" - }, - { - "name": "arbitrary", + "name": "gas_limit", "layout": { - "kind": "String" + "name": "N.t", + "kind": "Ref" }, "data_kind": { - "kind": "Variable" + "kind": "Dynamic" }, "kind": "named" - } - ], - "name": "Failing_noop" - }, - { - "tag": 20, - "fields": [ + }, { - "name": "Tag", + "name": "storage_limit", "layout": { - "size": "Uint8", - "kind": "Int" + "name": "N.t", + "kind": "Ref" }, "data_kind": { - "size": 1, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" }, { - "name": "slot", + "name": "balance", "layout": { - "size": "Uint16", - "kind": "Int" + "name": "N.t", + "kind": "Ref" }, "data_kind": { - "size": 2, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" }, { - "name": "level", - "layout": { - "size": "Int32", - "kind": "Int" - }, - "data_kind": { - "size": 4, - "kind": "Float" - }, - "kind": "named" + "kind": "option_indicator", + "name": "delegate" }, { - "name": "round", + "name": "delegate", "layout": { - "size": "Int32", - "kind": "Int" + "name": "public_key_hash", + "kind": "Ref" }, "data_kind": { - "size": 4, + "size": 21, "kind": "Float" }, "kind": "named" }, { - "name": "block_payload_hash", + "name": "script", "layout": { - "kind": "Bytes" + "name": "alpha.scripted.contracts", + "kind": "Ref" }, "data_kind": { - "size": 32, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" } ], - "name": "Preendorsement" + "name": "Origination" }, { - "tag": 21, + "tag": 110, "fields": [ { "name": "Tag", @@ -3795,57 +5025,82 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "slot", + "name": "source", "layout": { - "size": "Uint16", - "kind": "Int" + "name": "public_key_hash", + "kind": "Ref" }, "data_kind": { - "size": 2, + "size": 21, "kind": "Float" }, "kind": "named" }, { - "name": "level", + "name": "fee", "layout": { - "size": "Int32", - "kind": "Int" + "name": "N.t", + "kind": "Ref" + }, + "data_kind": { + "kind": "Dynamic" + }, + "kind": "named" + }, + { + "name": "counter", + "layout": { + "name": "N.t", + "kind": "Ref" + }, + "data_kind": { + "kind": "Dynamic" + }, + "kind": "named" + }, + { + "name": "gas_limit", + "layout": { + "name": "N.t", + "kind": "Ref" }, "data_kind": { - "size": 4, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" }, { - "name": "round", + "name": "storage_limit", "layout": { - "size": "Int32", - "kind": "Int" + "name": "N.t", + "kind": "Ref" }, "data_kind": { - "size": 4, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" }, { - "name": "block_payload_hash", + "kind": "option_indicator", + "name": "delegate" + }, + { + "name": "delegate", "layout": { - "kind": "Bytes" + "name": "public_key_hash", + "kind": "Ref" }, "data_kind": { - "size": 32, + "size": 21, "kind": "Float" }, "kind": "named" } ], - "name": "Endorsement" + "name": "Delegation" }, { - "tag": 107, + "tag": 111, "fields": [ { "name": "Tag", @@ -3916,21 +5171,25 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "public_key", + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "value", "layout": { - "name": "public_key", - "kind": "Ref" + "kind": "Bytes" }, "data_kind": { - "kind": "Dynamic" + "kind": "Variable" }, "kind": "named" } ], - "name": "Reveal" + "name": "Register_global_constant" }, { - "tag": 108, + "tag": 112, "fields": [ { "name": "Tag", @@ -4001,7 +5260,11 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "amount", + "kind": "option_indicator", + "name": "limit" + }, + { + "name": "limit", "layout": { "name": "N.t", "kind": "Ref" @@ -4010,27 +5273,74 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "Dynamic" }, "kind": "named" + } + ], + "name": "Set_deposits_limit" + }, + { + "tag": 150, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" }, { - "name": "destination", + "name": "source", "layout": { - "name": "alpha.transaction_destination", + "name": "public_key_hash", "kind": "Ref" }, "data_kind": { - "size": 22, + "size": 21, "kind": "Float" }, "kind": "named" }, { - "kind": "option_indicator", - "name": "parameters" + "name": "fee", + "layout": { + "name": "N.t", + "kind": "Ref" + }, + "data_kind": { + "kind": "Dynamic" + }, + "kind": "named" }, { - "name": "parameters", + "name": "counter", "layout": { - "name": "X_3", + "name": "N.t", + "kind": "Ref" + }, + "data_kind": { + "kind": "Dynamic" + }, + "kind": "named" + }, + { + "name": "gas_limit", + "layout": { + "name": "N.t", + "kind": "Ref" + }, + "data_kind": { + "kind": "Dynamic" + }, + "kind": "named" + }, + { + "name": "storage_limit", + "layout": { + "name": "N.t", "kind": "Ref" }, "data_kind": { @@ -4039,10 +5349,10 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" } ], - "name": "Transaction" + "name": "Tx_rollup_origination" }, { - "tag": 109, + "tag": 151, "fields": [ { "name": "Tag", @@ -4113,48 +5423,36 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "balance", + "name": "rollup", "layout": { - "name": "N.t", - "kind": "Ref" + "kind": "Bytes" }, "data_kind": { - "kind": "Dynamic" + "size": 20, + "kind": "Float" }, "kind": "named" }, { - "kind": "option_indicator", - "name": "delegate" - }, - { - "name": "delegate", - "layout": { - "name": "public_key_hash", - "kind": "Ref" - }, - "data_kind": { - "size": 21, - "kind": "Float" - }, - "kind": "named" + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" }, { - "name": "script", + "name": "content", "layout": { - "name": "alpha.scripted.contracts", - "kind": "Ref" + "kind": "String" }, "data_kind": { - "kind": "Dynamic" + "kind": "Variable" }, "kind": "named" } ], - "name": "Origination" + "name": "Tx_rollup_submit_batch" }, { - "tag": 110, + "tag": 152, "fields": [ { "name": "Tag", @@ -4225,26 +5523,32 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "kind": "option_indicator", - "name": "delegate" + "name": "rollup", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 20, + "kind": "Float" + }, + "kind": "named" }, { - "name": "delegate", + "name": "commitment", "layout": { - "name": "public_key_hash", + "name": "X_6", "kind": "Ref" }, "data_kind": { - "size": 21, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" } ], - "name": "Delegation" + "name": "Tx_rollup_commit" }, { - "tag": 111, + "tag": 153, "fields": [ { "name": "Tag", @@ -4315,25 +5619,21 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "kind": "dyn", - "num_fields": 1, - "size": "Uint30" - }, - { - "name": "value", + "name": "rollup", "layout": { "kind": "Bytes" }, "data_kind": { - "kind": "Variable" + "size": 20, + "kind": "Float" }, "kind": "named" } ], - "name": "Register_global_constant" + "name": "Tx_rollup_return_bond" }, { - "tag": 112, + "tag": 154, "fields": [ { "name": "Tag", @@ -4404,76 +5704,56 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "kind": "option_indicator", - "name": "limit" - }, - { - "name": "limit", - "layout": { - "name": "N.t", - "kind": "Ref" - }, - "data_kind": { - "kind": "Dynamic" - }, - "kind": "named" - } - ], - "name": "Set_deposits_limit" - }, - { - "tag": 150, - "fields": [ - { - "name": "Tag", + "name": "rollup", "layout": { - "size": "Uint8", - "kind": "Int" + "kind": "Bytes" }, "data_kind": { - "size": 1, + "size": 20, "kind": "Float" }, "kind": "named" }, { - "name": "source", + "name": "level", "layout": { - "name": "public_key_hash", - "kind": "Ref" + "size": "Int32", + "kind": "Int" }, "data_kind": { - "size": 21, + "size": 4, "kind": "Float" }, "kind": "named" }, { - "name": "fee", + "name": "hash", "layout": { - "name": "N.t", - "kind": "Ref" + "kind": "Bytes" }, "data_kind": { - "kind": "Dynamic" + "size": 32, + "kind": "Float" }, "kind": "named" }, { - "name": "counter", + "name": "batch_index", "layout": { - "name": "N.t", - "kind": "Ref" + "min": -1073741824, + "max": 1073741823, + "kind": "RangedInt" }, "data_kind": { - "kind": "Dynamic" + "size": 4, + "kind": "Float" }, "kind": "named" }, { - "name": "gas_limit", + "name": "batch", "layout": { - "name": "N.t", + "name": "X_5", "kind": "Ref" }, "data_kind": { @@ -4482,21 +5762,22 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "storage_limit", + "name": "nonce", "layout": { - "name": "N.t", - "kind": "Ref" + "size": "Int64", + "kind": "Int" }, "data_kind": { - "kind": "Dynamic" + "size": 8, + "kind": "Float" }, "kind": "named" } ], - "name": "Tx_rollup_origination" + "name": "Tx_rollup_rejection" }, { - "tag": 151, + "tag": 155, "fields": [ { "name": "Tag", @@ -4567,33 +5848,18 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "rollup", - "layout": { - "kind": "Bytes" - }, - "data_kind": { - "size": 20, - "kind": "Float" - }, - "kind": "named" - }, - { - "kind": "dyn", - "num_fields": 1, - "size": "Uint30" - }, - { - "name": "content", + "name": "hash", "layout": { - "kind": "String" + "kind": "Bytes" }, "data_kind": { - "kind": "Variable" + "size": 20, + "kind": "Float" }, "kind": "named" } ], - "name": "Tx_rollup_submit_batch" + "name": "Tx_rollup_prerejection" }, { "tag": 200, @@ -5457,6 +6723,10 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' } ], "definitions": { + "Commitment_hash": { + "title": "A commitment ID (Base58Check-encoded)", + "$ref": "#/definitions/unistring" + }, "Context_hash": { "title": "A hash of context (Base58Check-encoded)", "$ref": "#/definitions/unistring" @@ -5477,6 +6747,10 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "title": "A Tezos protocol ID (Base58Check-encoded)", "$ref": "#/definitions/unistring" }, + "Rejection_hash": { + "title": "A rejection ID (Base58Check-encoded)", + "$ref": "#/definitions/unistring" + }, "Signature": { "title": "A Ed25519, Secp256k1 or P256 signature (Base58Check-encoded)", "$ref": "#/definitions/unistring" @@ -5489,6 +6763,10 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "title": "A Ed25519, Secp256k1, or P256 public key hash (Base58Check-encoded)", "$ref": "#/definitions/unistring" }, + "Tx_rollup_l2_address": { + "title": "The hash of a BLS public key used to identify a L2 ticket holders (Base58Check-encoded)", + "$ref": "#/definitions/unistring" + }, "alpha.block_header.alpha.full_header": { "title": "Shell header", "description": "Block header's shell-related content. It contains information such as the block level, its predecessor and timestamp.", @@ -5563,6 +6841,11 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' ], "additionalProperties": false }, + "alpha.contract_id": { + "title": "A contract handle", + "description": "A contract notation as given to an RPC or inside scripts. Can be a base58 implicit contract hash or a base58 originated contract hash.", + "$ref": "#/definitions/unistring" + }, "alpha.entrypoint": { "title": "entrypoint", "description": "Named entrypoint to a Michelson smart contract", @@ -5742,14 +7025,14 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "False", "DUG", "DIG", - "chest_key", + "ticket", "BLAKE2B", "list", - "bls12_381_g1", + "never", "Pair", "INT", "nat", - "never", + "chain_id", "storage", "SIZE", "view", @@ -5766,15 +7049,15 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "operation", "MAP", "option", - "bls12_381_fr", + "bls12_381_g2", "ADD", "IMPLICIT_ACCOUNT", "SHA512", "int", "LSL", - "bls12_381_g2", - "ticket", - "sapling_transaction", + "bls12_381_g1", + "bls12_381_fr", + "tx_rollup_l2_address", "COMPARE", "SWAP", "STEPS_TO_QUOTA", @@ -5782,6 +7065,7 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "pair", "BALANCE", "CONCAT", + "constant", "MUL", "FAILWITH", "Elt", @@ -5840,7 +7124,7 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "PACK", "IF_CONS", "KECCAK", - "chest", + "chest_key", "UNIT", "EMPTY_SET", "NEQ", @@ -5852,7 +7136,7 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "contract", "LSR", "EMPTY_BIG_MAP", - "sapling_state", + "sapling_transaction", "JOIN_TICKETS", "LEVEL", "UNPAIR", @@ -5860,8 +7144,8 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "PUSH", "big_map", "GT", - "chain_id", - "constant", + "sapling_state", + "chest", "NOW", "IF_NONE", "PAIR", @@ -6677,6 +7961,314 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' ], "additionalProperties": false }, + { + "title": "Tx_rollup_commit", + "type": "object", + "properties": { + "kind": { + "type": "string", + "enum": [ + "tx_rollup_commit" + ] + }, + "source": { + "$ref": "#/definitions/Signature.Public_key_hash" + }, + "fee": { + "$ref": "#/definitions/alpha.mutez" + }, + "counter": { + "$ref": "#/definitions/positive_bignum" + }, + "gas_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "storage_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "rollup": { + "$ref": "#/definitions/alpha.tx_rollup_id" + }, + "commitment": { + "type": "object", + "properties": { + "level": { + "type": "integer", + "minimum": -2147483648, + "maximum": 2147483647 + }, + "batches": { + "type": "array", + "items": { + "type": "object", + "properties": { + "effects": { + "type": "array", + "items": { + "type": "object", + "properties": { + "contract": { + "$ref": "#/definitions/alpha.contract_id" + }, + "ticket": { + "$ref": "#/definitions/script_expr" + }, + "amount": { + "$ref": "#/definitions/int64" + } + }, + "required": [ + "amount", + "ticket", + "contract" + ], + "additionalProperties": false + } + }, + "root": { + "type": "string", + "pattern": "^([a-zA-Z0-9][a-zA-Z0-9])*$" + } + }, + "required": [ + "root", + "effects" + ], + "additionalProperties": false + } + }, + "predecessor": { + "oneOf": [ + { + "title": "Some", + "$ref": "#/definitions/Commitment_hash" + }, + { + "title": "None", + "type": "null" + } + ] + } + }, + "required": [ + "predecessor", + "batches", + "level" + ], + "additionalProperties": false + } + }, + "required": [ + "commitment", + "rollup", + "storage_limit", + "gas_limit", + "counter", + "fee", + "source", + "kind" + ], + "additionalProperties": false + }, + { + "title": "Tx_rollup_return_bond", + "type": "object", + "properties": { + "kind": { + "type": "string", + "enum": [ + "tx_rollup_return_bond" + ] + }, + "source": { + "$ref": "#/definitions/Signature.Public_key_hash" + }, + "fee": { + "$ref": "#/definitions/alpha.mutez" + }, + "counter": { + "$ref": "#/definitions/positive_bignum" + }, + "gas_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "storage_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "rollup": { + "$ref": "#/definitions/alpha.tx_rollup_id" + } + }, + "required": [ + "rollup", + "storage_limit", + "gas_limit", + "counter", + "fee", + "source", + "kind" + ], + "additionalProperties": false + }, + { + "title": "Tx_rollup_rejection", + "type": "object", + "properties": { + "kind": { + "type": "string", + "enum": [ + "tx_rollup_rejection" + ] + }, + "source": { + "$ref": "#/definitions/Signature.Public_key_hash" + }, + "fee": { + "$ref": "#/definitions/alpha.mutez" + }, + "counter": { + "$ref": "#/definitions/positive_bignum" + }, + "gas_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "storage_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "rollup": { + "$ref": "#/definitions/alpha.tx_rollup_id" + }, + "level": { + "type": "integer", + "minimum": -2147483648, + "maximum": 2147483647 + }, + "hash": { + "$ref": "#/definitions/Commitment_hash" + }, + "batch_index": { + "type": "integer", + "minimum": -1073741824, + "maximum": 1073741823 + }, + "batch": { + "oneOf": [ + { + "title": "Batch", + "type": "object", + "properties": { + "batch": { + "$ref": "#/definitions/unistring" + } + }, + "required": [ + "batch" + ], + "additionalProperties": false + }, + { + "title": "Deposit", + "type": "object", + "properties": { + "deposit": { + "type": "object", + "properties": { + "destination": { + "oneOf": [ + { + "title": "Key", + "type": "integer", + "minimum": -2147483648, + "maximum": 2147483647 + }, + { + "title": "Value", + "$ref": "#/definitions/Tx_rollup_l2_address" + } + ] + }, + "ticket_hash": { + "$ref": "#/definitions/script_expr" + }, + "amount": { + "$ref": "#/definitions/int64" + } + }, + "required": [ + "amount", + "ticket_hash", + "destination" + ], + "additionalProperties": false + } + }, + "required": [ + "deposit" + ], + "additionalProperties": false + } + ] + }, + "nonce": { + "$ref": "#/definitions/int64" + } + }, + "required": [ + "nonce", + "batch", + "batch_index", + "hash", + "level", + "rollup", + "storage_limit", + "gas_limit", + "counter", + "fee", + "source", + "kind" + ], + "additionalProperties": false + }, + { + "title": "Tx_rollup_prerejection", + "type": "object", + "properties": { + "kind": { + "type": "string", + "enum": [ + "tx_rollup_prerejection" + ] + }, + "source": { + "$ref": "#/definitions/Signature.Public_key_hash" + }, + "fee": { + "$ref": "#/definitions/alpha.mutez" + }, + "counter": { + "$ref": "#/definitions/positive_bignum" + }, + "gas_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "storage_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "hash": { + "$ref": "#/definitions/Rejection_hash" + } + }, + "required": [ + "hash", + "storage_limit", + "gas_limit", + "counter", + "fee", + "source", + "kind" + ], + "additionalProperties": false + }, { "title": "Sc_rollup_originate", "type": "object", @@ -6945,7 +8537,7 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' }, "alpha.transaction_destination": { "title": "A destination of a transaction", - "description": "A destination notation compatible with the contract notation as given to an RPC or inside scripts. Can be a base58 implicit contract hash or a base58 originated contract hash.", + "description": "A destination notation compatible with the contract notation as given to an RPC or inside scripts. Can be a base58 implicit contract hash, a base58 originated contract hash, or a base58 originated transaction rollup.", "$ref": "#/definitions/unistring" }, "alpha.tx_rollup_id": { @@ -6978,6 +8570,11 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "pattern": "^([a-zA-Z0-9][a-zA-Z0-9])*$" } }, + "int64": { + "title": "64 bit integers", + "description": "Decimal representation of 64 bit integers", + "type": "string" + }, "micheline.alpha.michelson_v1.expression": { "oneOf": [ { @@ -7091,6 +8688,10 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "description": "Decimal representation of a positive big number", "type": "string" }, + "script_expr": { + "title": "A script expression ID (Base58Check-encoded)", + "$ref": "#/definitions/unistring" + }, "timestamp.protocol": { "description": "A timestamp as seen by the protocol: second-level precision, epoch based.", "$ref": "#/definitions/unistring" diff --git a/tezt/_regressions/rpc/alpha.client.others.out b/tezt/_regressions/rpc/alpha.client.others.out index e945ddd84cbcb748c56814357e51f4a23c82a927..52ab8b42f94c1de556854e07d2013cbbb52a25f9 100644 --- a/tezt/_regressions/rpc/alpha.client.others.out +++ b/tezt/_regressions/rpc/alpha.client.others.out @@ -31,7 +31,8 @@ tezt/_regressions/rpc/alpha.client.others.out "cache_stake_distribution_cycles": 8, "cache_sampler_state_cycles": 8, "tx_rollup_enable": false, "tx_rollup_origination_size": 60000, "tx_rollup_hard_size_limit_per_inbox": 100000, - "tx_rollup_hard_size_limit_per_message": 5000, "sc_rollup_enable": false, + "tx_rollup_hard_size_limit_per_message": 5000, + "tx_rollup_commitment_bond": "10000000000", "sc_rollup_enable": false, "sc_rollup_origination_size": 6314 } ./tezos-client rpc get /chains/main/blocks/head/helpers/baking_rights diff --git a/tezt/_regressions/rpc/alpha.light.others.out b/tezt/_regressions/rpc/alpha.light.others.out index b9f4dcb1d13875a830a5582ea62967807a8bcc94..5462a3a58b1eb5bdeefa7627e40492f84afb9c94 100644 --- a/tezt/_regressions/rpc/alpha.light.others.out +++ b/tezt/_regressions/rpc/alpha.light.others.out @@ -32,7 +32,8 @@ protocol of light mode unspecified, using the node's protocol: ProtoGenesisGenes "cache_stake_distribution_cycles": 8, "cache_sampler_state_cycles": 8, "tx_rollup_enable": false, "tx_rollup_origination_size": 60000, "tx_rollup_hard_size_limit_per_inbox": 100000, - "tx_rollup_hard_size_limit_per_message": 5000, "sc_rollup_enable": false, + "tx_rollup_hard_size_limit_per_message": 5000, + "tx_rollup_commitment_bond": "10000000000", "sc_rollup_enable": false, "sc_rollup_origination_size": 6314 } ./tezos-client --mode light rpc get /chains/main/blocks/head/helpers/baking_rights diff --git a/tezt/_regressions/rpc/alpha.proxy.mempool.out b/tezt/_regressions/rpc/alpha.proxy.mempool.out index e23a8d85fd5a5e9590113f6234121b723f90b6b7..c2778b1ad6f537bd2f8fcb1a06c7be2e3d11bb73 100644 --- a/tezt/_regressions/rpc/alpha.proxy.mempool.out +++ b/tezt/_regressions/rpc/alpha.proxy.mempool.out @@ -593,6 +593,10 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "additionalProperties": false }, "definitions": { + "Commitment_hash": { + "title": "A commitment ID (Base58Check-encoded)", + "$ref": "#/definitions/unistring" + }, "Context_hash": { "title": "A hash of context (Base58Check-encoded)", "$ref": "#/definitions/unistring" @@ -613,6 +617,10 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "title": "A Tezos protocol ID (Base58Check-encoded)", "$ref": "#/definitions/unistring" }, + "Rejection_hash": { + "title": "A rejection ID (Base58Check-encoded)", + "$ref": "#/definitions/unistring" + }, "Signature": { "title": "A Ed25519, Secp256k1 or P256 signature (Base58Check-encoded)", "$ref": "#/definitions/unistring" @@ -625,6 +633,10 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "title": "A Ed25519, Secp256k1, or P256 public key hash (Base58Check-encoded)", "$ref": "#/definitions/unistring" }, + "Tx_rollup_l2_address": { + "title": "The hash of a BLS public key used to identify a L2 ticket holders (Base58Check-encoded)", + "$ref": "#/definitions/unistring" + }, "alpha.block_header.alpha.full_header": { "title": "Shell header", "description": "Block header's shell-related content. It contains information such as the block level, its predecessor and timestamp.", @@ -699,6 +711,11 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' ], "additionalProperties": false }, + "alpha.contract_id": { + "title": "A contract handle", + "description": "A contract notation as given to an RPC or inside scripts. Can be a base58 implicit contract hash or a base58 originated contract hash.", + "$ref": "#/definitions/unistring" + }, "alpha.entrypoint": { "title": "entrypoint", "description": "Named entrypoint to a Michelson smart contract", @@ -878,14 +895,14 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "False", "DUG", "DIG", - "chest_key", + "ticket", "BLAKE2B", "list", - "bls12_381_g1", + "never", "Pair", "INT", "nat", - "never", + "chain_id", "storage", "SIZE", "view", @@ -902,15 +919,15 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "operation", "MAP", "option", - "bls12_381_fr", + "bls12_381_g2", "ADD", "IMPLICIT_ACCOUNT", "SHA512", "int", "LSL", - "bls12_381_g2", - "ticket", - "sapling_transaction", + "bls12_381_g1", + "bls12_381_fr", + "tx_rollup_l2_address", "COMPARE", "SWAP", "STEPS_TO_QUOTA", @@ -918,6 +935,7 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "pair", "BALANCE", "CONCAT", + "constant", "MUL", "FAILWITH", "Elt", @@ -976,7 +994,7 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "PACK", "IF_CONS", "KECCAK", - "chest", + "chest_key", "UNIT", "EMPTY_SET", "NEQ", @@ -988,7 +1006,7 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "contract", "LSR", "EMPTY_BIG_MAP", - "sapling_state", + "sapling_transaction", "JOIN_TICKETS", "LEVEL", "UNPAIR", @@ -996,8 +1014,8 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "PUSH", "big_map", "GT", - "chain_id", - "constant", + "sapling_state", + "chest", "NOW", "IF_NONE", "PAIR", @@ -1813,6 +1831,314 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' ], "additionalProperties": false }, + { + "title": "Tx_rollup_commit", + "type": "object", + "properties": { + "kind": { + "type": "string", + "enum": [ + "tx_rollup_commit" + ] + }, + "source": { + "$ref": "#/definitions/Signature.Public_key_hash" + }, + "fee": { + "$ref": "#/definitions/alpha.mutez" + }, + "counter": { + "$ref": "#/definitions/positive_bignum" + }, + "gas_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "storage_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "rollup": { + "$ref": "#/definitions/alpha.tx_rollup_id" + }, + "commitment": { + "type": "object", + "properties": { + "level": { + "type": "integer", + "minimum": -2147483648, + "maximum": 2147483647 + }, + "batches": { + "type": "array", + "items": { + "type": "object", + "properties": { + "effects": { + "type": "array", + "items": { + "type": "object", + "properties": { + "contract": { + "$ref": "#/definitions/alpha.contract_id" + }, + "ticket": { + "$ref": "#/definitions/script_expr" + }, + "amount": { + "$ref": "#/definitions/int64" + } + }, + "required": [ + "amount", + "ticket", + "contract" + ], + "additionalProperties": false + } + }, + "root": { + "type": "string", + "pattern": "^([a-zA-Z0-9][a-zA-Z0-9])*$" + } + }, + "required": [ + "root", + "effects" + ], + "additionalProperties": false + } + }, + "predecessor": { + "oneOf": [ + { + "title": "Some", + "$ref": "#/definitions/Commitment_hash" + }, + { + "title": "None", + "type": "null" + } + ] + } + }, + "required": [ + "predecessor", + "batches", + "level" + ], + "additionalProperties": false + } + }, + "required": [ + "commitment", + "rollup", + "storage_limit", + "gas_limit", + "counter", + "fee", + "source", + "kind" + ], + "additionalProperties": false + }, + { + "title": "Tx_rollup_return_bond", + "type": "object", + "properties": { + "kind": { + "type": "string", + "enum": [ + "tx_rollup_return_bond" + ] + }, + "source": { + "$ref": "#/definitions/Signature.Public_key_hash" + }, + "fee": { + "$ref": "#/definitions/alpha.mutez" + }, + "counter": { + "$ref": "#/definitions/positive_bignum" + }, + "gas_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "storage_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "rollup": { + "$ref": "#/definitions/alpha.tx_rollup_id" + } + }, + "required": [ + "rollup", + "storage_limit", + "gas_limit", + "counter", + "fee", + "source", + "kind" + ], + "additionalProperties": false + }, + { + "title": "Tx_rollup_rejection", + "type": "object", + "properties": { + "kind": { + "type": "string", + "enum": [ + "tx_rollup_rejection" + ] + }, + "source": { + "$ref": "#/definitions/Signature.Public_key_hash" + }, + "fee": { + "$ref": "#/definitions/alpha.mutez" + }, + "counter": { + "$ref": "#/definitions/positive_bignum" + }, + "gas_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "storage_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "rollup": { + "$ref": "#/definitions/alpha.tx_rollup_id" + }, + "level": { + "type": "integer", + "minimum": -2147483648, + "maximum": 2147483647 + }, + "hash": { + "$ref": "#/definitions/Commitment_hash" + }, + "batch_index": { + "type": "integer", + "minimum": -1073741824, + "maximum": 1073741823 + }, + "batch": { + "oneOf": [ + { + "title": "Batch", + "type": "object", + "properties": { + "batch": { + "$ref": "#/definitions/unistring" + } + }, + "required": [ + "batch" + ], + "additionalProperties": false + }, + { + "title": "Deposit", + "type": "object", + "properties": { + "deposit": { + "type": "object", + "properties": { + "destination": { + "oneOf": [ + { + "title": "Key", + "type": "integer", + "minimum": -2147483648, + "maximum": 2147483647 + }, + { + "title": "Value", + "$ref": "#/definitions/Tx_rollup_l2_address" + } + ] + }, + "ticket_hash": { + "$ref": "#/definitions/script_expr" + }, + "amount": { + "$ref": "#/definitions/int64" + } + }, + "required": [ + "amount", + "ticket_hash", + "destination" + ], + "additionalProperties": false + } + }, + "required": [ + "deposit" + ], + "additionalProperties": false + } + ] + }, + "nonce": { + "$ref": "#/definitions/int64" + } + }, + "required": [ + "nonce", + "batch", + "batch_index", + "hash", + "level", + "rollup", + "storage_limit", + "gas_limit", + "counter", + "fee", + "source", + "kind" + ], + "additionalProperties": false + }, + { + "title": "Tx_rollup_prerejection", + "type": "object", + "properties": { + "kind": { + "type": "string", + "enum": [ + "tx_rollup_prerejection" + ] + }, + "source": { + "$ref": "#/definitions/Signature.Public_key_hash" + }, + "fee": { + "$ref": "#/definitions/alpha.mutez" + }, + "counter": { + "$ref": "#/definitions/positive_bignum" + }, + "gas_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "storage_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "hash": { + "$ref": "#/definitions/Rejection_hash" + } + }, + "required": [ + "hash", + "storage_limit", + "gas_limit", + "counter", + "fee", + "source", + "kind" + ], + "additionalProperties": false + }, { "title": "Sc_rollup_originate", "type": "object", @@ -2081,7 +2407,7 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' }, "alpha.transaction_destination": { "title": "A destination of a transaction", - "description": "A destination notation compatible with the contract notation as given to an RPC or inside scripts. Can be a base58 implicit contract hash or a base58 originated contract hash.", + "description": "A destination notation compatible with the contract notation as given to an RPC or inside scripts. Can be a base58 implicit contract hash, a base58 originated contract hash, or a base58 originated transaction rollup.", "$ref": "#/definitions/unistring" }, "alpha.tx_rollup_id": { @@ -2114,6 +2440,11 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "pattern": "^([a-zA-Z0-9][a-zA-Z0-9])*$" } }, + "int64": { + "title": "64 bit integers", + "description": "Decimal representation of 64 bit integers", + "type": "string" + }, "micheline.alpha.michelson_v1.expression": { "oneOf": [ { @@ -2196,6 +2527,10 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "description": "Decimal representation of a positive big number", "type": "string" }, + "script_expr": { + "title": "A script expression ID (Base58Check-encoded)", + "$ref": "#/definitions/unistring" + }, "timestamp.protocol": { "description": "A timestamp as seen by the protocol: second-level precision, epoch based.", "$ref": "#/definitions/unistring" @@ -2323,54 +2658,14 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' }, { "description": { - "title": "alpha.scripted.contracts" + "title": "X_4" }, "encoding": { - "fields": [ - { - "kind": "dyn", - "num_fields": 1, - "size": "Uint30" - }, - { - "name": "code", - "layout": { - "kind": "Bytes" - }, - "data_kind": { - "kind": "Variable" - }, - "kind": "named" - }, - { - "kind": "dyn", - "num_fields": 1, - "size": "Uint30" - }, - { - "name": "storage", - "layout": { - "kind": "Bytes" - }, - "data_kind": { - "kind": "Variable" - }, - "kind": "named" - } - ] - } - }, - { - "description": { - "title": "alpha.transaction_destination" - }, - "encoding": { - "tag_size": "Uint8", - "kind": { - "size": 22, - "kind": "Float" - }, - "cases": [ + "tag_size": "Uint8", + "kind": { + "kind": "Dynamic" + }, + "cases": [ { "tag": 0, "fields": [ @@ -2387,19 +2682,18 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "Signature.Public_key_hash", "layout": { - "name": "public_key_hash", - "kind": "Ref" + "size": "Int32", + "kind": "Int" }, + "kind": "anon", "data_kind": { - "size": 21, + "size": 4, "kind": "Float" - }, - "kind": "named" + } } ], - "name": "Implicit" + "name": "Key" }, { "tag": 1, @@ -2417,7 +2711,7 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "Contract_hash", + "name": "Tx_rollup_l2_address", "layout": { "kind": "Bytes" }, @@ -2426,27 +2720,59 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "Float" }, "kind": "named" - }, - { - "name": "padding", - "layout": { - "kind": "Padding" - }, - "data_kind": { - "size": 1, - "kind": "Float" - }, - "kind": "named" } ], - "name": "Originated" + "name": "Value" } ] } }, { "description": { - "title": "alpha.entrypoint" + "title": "X_3" + }, + "encoding": { + "fields": [ + { + "name": "destination", + "layout": { + "name": "X_4", + "kind": "Ref" + }, + "data_kind": { + "kind": "Dynamic" + }, + "kind": "named" + }, + { + "name": "ticket_hash", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 32, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "amount", + "layout": { + "size": "Int64", + "kind": "Int" + }, + "data_kind": { + "size": 8, + "kind": "Float" + }, + "kind": "named" + } + ] + } + }, + { + "description": { + "title": "X_5" }, "encoding": { "tag_size": "Uint8", @@ -2470,17 +2796,22 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "batch", "layout": { - "kind": "Zero_width" + "kind": "String" }, - "kind": "anon", "data_kind": { - "size": 0, - "kind": "Float" - } + "kind": "Variable" + }, + "kind": "named" } ], - "name": "default" + "name": "Batch" }, { "tag": 1, @@ -2498,20 +2829,35 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { + "name": "deposit", "layout": { - "kind": "Zero_width" + "name": "X_3", + "kind": "Ref" }, - "kind": "anon", "data_kind": { - "size": 0, - "kind": "Float" - } + "kind": "Dynamic" + }, + "kind": "named" } ], - "name": "root" - }, + "name": "Deposit" + } + ] + } + }, + { + "description": { + "title": "alpha.contract_id" + }, + "encoding": { + "tag_size": "Uint8", + "kind": { + "size": 22, + "kind": "Float" + }, + "cases": [ { - "tag": 2, + "tag": 0, "fields": [ { "name": "Tag", @@ -2526,20 +2872,22 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { + "name": "Signature.Public_key_hash", "layout": { - "kind": "Zero_width" + "name": "public_key_hash", + "kind": "Ref" }, - "kind": "anon", "data_kind": { - "size": 0, + "size": 21, "kind": "Float" - } + }, + "kind": "named" } ], - "name": "do" + "name": "Implicit" }, { - "tag": 3, + "tag": 1, "fields": [ { "name": "Tag", @@ -2554,110 +2902,71 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { + "name": "Contract_hash", "layout": { - "kind": "Zero_width" - }, - "kind": "anon", - "data_kind": { - "size": 0, - "kind": "Float" - } - } - ], - "name": "set_delegate" - }, - { - "tag": 4, - "fields": [ - { - "name": "Tag", - "layout": { - "size": "Uint8", - "kind": "Int" + "kind": "Bytes" }, "data_kind": { - "size": 1, + "size": 20, "kind": "Float" }, "kind": "named" }, { + "name": "padding", "layout": { - "kind": "Zero_width" - }, - "kind": "anon", - "data_kind": { - "size": 0, - "kind": "Float" - } - } - ], - "name": "remove_delegate" - }, - { - "tag": 255, - "fields": [ - { - "name": "Tag", - "layout": { - "size": "Uint8", - "kind": "Int" + "kind": "Padding" }, "data_kind": { "size": 1, "kind": "Float" }, "kind": "named" - }, - { - "kind": "dyn", - "num_fields": 1, - "size": "Uint8" - }, - { - "layout": { - "kind": "String" - }, - "kind": "anon", - "data_kind": { - "kind": "Variable" - } } ], - "name": "named" + "name": "Originated" } ] } }, { "description": { - "title": "X_3" + "title": "X_8" }, "encoding": { "fields": [ { - "name": "entrypoint", + "name": "contract", "layout": { - "name": "alpha.entrypoint", + "name": "alpha.contract_id", "kind": "Ref" }, "data_kind": { - "kind": "Dynamic" + "size": 22, + "kind": "Float" }, "kind": "named" }, { - "kind": "dyn", - "num_fields": 1, - "size": "Uint30" + "name": "ticket", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 32, + "kind": "Float" + }, + "kind": "named" }, { - "name": "value", + "name": "amount", "layout": { - "kind": "Bytes" + "size": "Int64", + "kind": "Int" }, "data_kind": { - "kind": "Variable" + "size": 8, + "kind": "Float" }, "kind": "named" } @@ -2666,18 +2975,41 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' }, { "description": { - "title": "N.t", - "description": "A variable-length sequence of bytes encoding a Zarith natural number. Each byte has a running unary size bit: the most significant bit of each byte indicates whether this is the last byte in the sequence (0) or whether the sequence continues (1). Size bits ignored, the data is the binary representation of the number in little-endian order." + "title": "X_7" }, "encoding": { "fields": [ { - "name": "N.t", - "layout": { - "kind": "Bytes" - }, - "data_kind": { - "kind": "Dynamic" + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "effects", + "layout": { + "layout": { + "name": "X_8", + "kind": "Ref" + }, + "kind": "Seq" + }, + "data_kind": { + "kind": "Variable" + }, + "kind": "named" + }, + { + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "root", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "kind": "Variable" }, "kind": "named" } @@ -2686,7 +3018,7 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' }, { "description": { - "title": "public_key" + "title": "X_9" }, "encoding": { "tag_size": "Uint8", @@ -2710,18 +3042,17 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "Ed25519.Public_key", "layout": { - "kind": "Bytes" + "kind": "Zero_width" }, + "kind": "anon", "data_kind": { - "size": 32, + "size": 0, "kind": "Float" - }, - "kind": "named" + } } ], - "name": "Ed25519" + "name": "None" }, { "tag": 1, @@ -2739,161 +3070,101 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "Secp256k1.Public_key", - "layout": { - "kind": "Bytes" - }, - "data_kind": { - "size": 33, - "kind": "Float" - }, - "kind": "named" - } - ], - "name": "Secp256k1" - }, - { - "tag": 2, - "fields": [ - { - "name": "Tag", - "layout": { - "size": "Uint8", - "kind": "Int" - }, - "data_kind": { - "size": 1, - "kind": "Float" - }, - "kind": "named" - }, - { - "name": "P256.Public_key", + "name": "Commitment_hash", "layout": { "kind": "Bytes" }, "data_kind": { - "size": 33, + "size": 32, "kind": "Float" }, "kind": "named" } ], - "name": "P256" + "name": "Some" } ] } }, { "description": { - "title": "alpha.inlined.preendorsement.contents" + "title": "X_6" }, "encoding": { - "tag_size": "Uint8", - "kind": { - "size": 43, - "kind": "Float" - }, - "cases": [ + "fields": [ { - "tag": 20, - "fields": [ - { - "name": "Tag", - "layout": { - "size": "Uint8", - "kind": "Int" - }, - "data_kind": { - "size": 1, - "kind": "Float" - }, - "kind": "named" - }, - { - "name": "slot", - "layout": { - "size": "Uint16", - "kind": "Int" - }, - "data_kind": { - "size": 2, - "kind": "Float" - }, - "kind": "named" - }, - { - "name": "level", - "layout": { - "size": "Int32", - "kind": "Int" - }, - "data_kind": { - "size": 4, - "kind": "Float" - }, - "kind": "named" - }, - { - "name": "round", - "layout": { - "size": "Int32", - "kind": "Int" - }, - "data_kind": { - "size": 4, - "kind": "Float" - }, - "kind": "named" + "name": "level", + "layout": { + "size": "Int32", + "kind": "Int" + }, + "data_kind": { + "size": 4, + "kind": "Float" + }, + "kind": "named" + }, + { + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "batches", + "layout": { + "layout": { + "name": "X_7", + "kind": "Ref" }, - { - "name": "block_payload_hash", - "layout": { - "kind": "Bytes" - }, - "data_kind": { - "size": 32, - "kind": "Float" - }, - "kind": "named" - } - ], - "name": "Preendorsement" + "kind": "Seq" + }, + "data_kind": { + "kind": "Variable" + }, + "kind": "named" + }, + { + "name": "predecessor", + "layout": { + "name": "X_9", + "kind": "Ref" + }, + "data_kind": { + "kind": "Dynamic" + }, + "kind": "named" } ] } }, { "description": { - "title": "alpha.inlined.preendorsement" + "title": "alpha.scripted.contracts" }, "encoding": { "fields": [ { - "name": "branch", + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "code", "layout": { "kind": "Bytes" }, "data_kind": { - "size": 32, - "kind": "Float" + "kind": "Variable" }, "kind": "named" }, { - "name": "operations", - "layout": { - "name": "alpha.inlined.preendorsement.contents", - "kind": "Ref" - }, - "data_kind": { - "size": 43, - "kind": "Float" - }, - "kind": "named" + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" }, { - "name": "signature", + "name": "storage", "layout": { "kind": "Bytes" }, @@ -2907,12 +3178,12 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' }, { "description": { - "title": "public_key_hash" + "title": "alpha.transaction_destination" }, "encoding": { "tag_size": "Uint8", "kind": { - "size": 21, + "size": 22, "kind": "Float" }, "cases": [ @@ -2932,18 +3203,19 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "Ed25519.Public_key_hash", + "name": "Signature.Public_key_hash", "layout": { - "kind": "Bytes" + "name": "public_key_hash", + "kind": "Ref" }, "data_kind": { - "size": 20, + "size": 21, "kind": "Float" }, "kind": "named" } ], - "name": "Ed25519" + "name": "Implicit" }, { "tag": 1, @@ -2961,7 +3233,7 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "Secp256k1.Public_key_hash", + "name": "Contract_hash", "layout": { "kind": "Bytes" }, @@ -2970,9 +3242,20 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "Float" }, "kind": "named" + }, + { + "name": "padding", + "layout": { + "kind": "Padding" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" } ], - "name": "Secp256k1" + "name": "Originated" }, { "tag": 2, @@ -2990,7 +3273,7 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "P256.Public_key_hash", + "name": "Rollup_hash", "layout": { "kind": "Bytes" }, @@ -2999,145 +3282,451 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "Float" }, "kind": "named" + }, + { + "name": "padding", + "layout": { + "kind": "Padding" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" } ], - "name": "P256" + "name": "Tx_rollup" } ] } }, { "description": { - "title": "fitness.elem" + "title": "alpha.entrypoint" }, "encoding": { - "fields": [ + "tag_size": "Uint8", + "kind": { + "kind": "Dynamic" + }, + "cases": [ { - "kind": "dyn", - "num_fields": 1, - "size": "Uint30" + "tag": 0, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "layout": { + "kind": "Zero_width" + }, + "kind": "anon", + "data_kind": { + "size": 0, + "kind": "Float" + } + } + ], + "name": "default" }, { - "layout": { - "kind": "Bytes" - }, - "kind": "anon", - "data_kind": { - "kind": "Variable" - } + "tag": 1, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "layout": { + "kind": "Zero_width" + }, + "kind": "anon", + "data_kind": { + "size": 0, + "kind": "Float" + } + } + ], + "name": "root" + }, + { + "tag": 2, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "layout": { + "kind": "Zero_width" + }, + "kind": "anon", + "data_kind": { + "size": 0, + "kind": "Float" + } + } + ], + "name": "do" + }, + { + "tag": 3, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "layout": { + "kind": "Zero_width" + }, + "kind": "anon", + "data_kind": { + "size": 0, + "kind": "Float" + } + } + ], + "name": "set_delegate" + }, + { + "tag": 4, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "layout": { + "kind": "Zero_width" + }, + "kind": "anon", + "data_kind": { + "size": 0, + "kind": "Float" + } + } + ], + "name": "remove_delegate" + }, + { + "tag": 255, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "kind": "dyn", + "num_fields": 1, + "size": "Uint8" + }, + { + "layout": { + "kind": "String" + }, + "kind": "anon", + "data_kind": { + "kind": "Variable" + } + } + ], + "name": "named" } ] } }, { "description": { - "title": "alpha.block_header.alpha.full_header" + "title": "X_10" }, "encoding": { "fields": [ { - "name": "level", + "name": "entrypoint", "layout": { - "size": "Int32", - "kind": "Int" + "name": "alpha.entrypoint", + "kind": "Ref" }, "data_kind": { - "size": 4, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" }, { - "name": "proto", - "layout": { - "size": "Uint8", - "kind": "Int" - }, - "data_kind": { - "size": 1, - "kind": "Float" - }, - "kind": "named" + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" }, { - "name": "predecessor", + "name": "value", "layout": { "kind": "Bytes" }, "data_kind": { - "size": 32, - "kind": "Float" - }, - "kind": "named" - }, - { - "name": "timestamp", - "layout": { - "size": "Int64", - "kind": "Int" - }, - "data_kind": { - "size": 8, - "kind": "Float" - }, - "kind": "named" - }, - { - "name": "validation_pass", - "layout": { - "size": "Uint8", - "kind": "Int" - }, - "data_kind": { - "size": 1, - "kind": "Float" + "kind": "Variable" }, "kind": "named" - }, + } + ] + } + }, + { + "description": { + "title": "N.t", + "description": "A variable-length sequence of bytes encoding a Zarith natural number. Each byte has a running unary size bit: the most significant bit of each byte indicates whether this is the last byte in the sequence (0) or whether the sequence continues (1). Size bits ignored, the data is the binary representation of the number in little-endian order." + }, + "encoding": { + "fields": [ { - "name": "operations_hash", + "name": "N.t", "layout": { "kind": "Bytes" }, "data_kind": { - "size": 32, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" - }, - { - "kind": "dyn", - "name": "fitness", - "num_fields": 1, - "size": "Uint30" - }, - { - "name": "fitness", - "layout": { - "layout": { - "name": "fitness.elem", - "kind": "Ref" + } + ] + } + }, + { + "description": { + "title": "public_key" + }, + "encoding": { + "tag_size": "Uint8", + "kind": { + "kind": "Dynamic" + }, + "cases": [ + { + "tag": 0, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" }, - "kind": "Seq" - }, - "data_kind": { - "kind": "Variable" - }, - "kind": "named" + { + "name": "Ed25519.Public_key", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 32, + "kind": "Float" + }, + "kind": "named" + } + ], + "name": "Ed25519" }, { - "name": "context", - "layout": { - "kind": "Bytes" - }, - "data_kind": { - "size": 32, - "kind": "Float" - }, - "kind": "named" + "tag": 1, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "Secp256k1.Public_key", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 33, + "kind": "Float" + }, + "kind": "named" + } + ], + "name": "Secp256k1" }, { - "name": "payload_hash", + "tag": 2, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "P256.Public_key", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 33, + "kind": "Float" + }, + "kind": "named" + } + ], + "name": "P256" + } + ] + } + }, + { + "description": { + "title": "alpha.inlined.preendorsement.contents" + }, + "encoding": { + "tag_size": "Uint8", + "kind": { + "size": 43, + "kind": "Float" + }, + "cases": [ + { + "tag": 20, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "slot", + "layout": { + "size": "Uint16", + "kind": "Int" + }, + "data_kind": { + "size": 2, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "level", + "layout": { + "size": "Int32", + "kind": "Int" + }, + "data_kind": { + "size": 4, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "round", + "layout": { + "size": "Int32", + "kind": "Int" + }, + "data_kind": { + "size": 4, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "block_payload_hash", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 32, + "kind": "Float" + }, + "kind": "named" + } + ], + "name": "Preendorsement" + } + ] + } + }, + { + "description": { + "title": "alpha.inlined.preendorsement" + }, + "encoding": { + "fields": [ + { + "name": "branch", "layout": { "kind": "Bytes" }, @@ -3148,81 +3737,774 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "payload_round", - "layout": { - "size": "Int32", - "kind": "Int" - }, - "data_kind": { - "size": 4, - "kind": "Float" - }, - "kind": "named" - }, - { - "name": "proof_of_work_nonce", + "name": "operations", "layout": { - "kind": "Bytes" + "name": "alpha.inlined.preendorsement.contents", + "kind": "Ref" }, "data_kind": { - "size": 8, + "size": 43, "kind": "Float" }, "kind": "named" }, { - "kind": "option_indicator", - "name": "seed_nonce_hash" - }, - { - "name": "seed_nonce_hash", + "name": "signature", "layout": { "kind": "Bytes" }, "data_kind": { - "size": 32, - "kind": "Float" + "kind": "Variable" }, "kind": "named" - }, + } + ] + } + }, + { + "description": { + "title": "public_key_hash" + }, + "encoding": { + "tag_size": "Uint8", + "kind": { + "size": 21, + "kind": "Float" + }, + "cases": [ { - "name": "liquidity_baking_escape_vote", - "layout": { - "kind": "Bool" - }, - "data_kind": { - "size": 1, - "kind": "Float" - }, + "tag": 0, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "Ed25519.Public_key_hash", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 20, + "kind": "Float" + }, + "kind": "named" + } + ], + "name": "Ed25519" + }, + { + "tag": 1, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "Secp256k1.Public_key_hash", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 20, + "kind": "Float" + }, + "kind": "named" + } + ], + "name": "Secp256k1" + }, + { + "tag": 2, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "P256.Public_key_hash", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 20, + "kind": "Float" + }, + "kind": "named" + } + ], + "name": "P256" + } + ] + } + }, + { + "description": { + "title": "fitness.elem" + }, + "encoding": { + "fields": [ + { + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "layout": { + "kind": "Bytes" + }, + "kind": "anon", + "data_kind": { + "kind": "Variable" + } + } + ] + } + }, + { + "description": { + "title": "alpha.block_header.alpha.full_header" + }, + "encoding": { + "fields": [ + { + "name": "level", + "layout": { + "size": "Int32", + "kind": "Int" + }, + "data_kind": { + "size": 4, + "kind": "Float" + }, "kind": "named" }, { - "name": "signature", - "layout": { - "kind": "Bytes" - }, - "data_kind": { - "size": 64, - "kind": "Float" - }, - "kind": "named" - } - ] - } - }, - { - "description": { - "title": "alpha.inlined.endorsement_mempool.contents" - }, - "encoding": { - "tag_size": "Uint8", - "kind": { - "size": 43, - "kind": "Float" - }, - "cases": [ - { - "tag": 21, + "name": "proto", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "predecessor", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 32, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "timestamp", + "layout": { + "size": "Int64", + "kind": "Int" + }, + "data_kind": { + "size": 8, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "validation_pass", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "operations_hash", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 32, + "kind": "Float" + }, + "kind": "named" + }, + { + "kind": "dyn", + "name": "fitness", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "fitness", + "layout": { + "layout": { + "name": "fitness.elem", + "kind": "Ref" + }, + "kind": "Seq" + }, + "data_kind": { + "kind": "Variable" + }, + "kind": "named" + }, + { + "name": "context", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 32, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "payload_hash", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 32, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "payload_round", + "layout": { + "size": "Int32", + "kind": "Int" + }, + "data_kind": { + "size": 4, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "proof_of_work_nonce", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 8, + "kind": "Float" + }, + "kind": "named" + }, + { + "kind": "option_indicator", + "name": "seed_nonce_hash" + }, + { + "name": "seed_nonce_hash", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 32, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "liquidity_baking_escape_vote", + "layout": { + "kind": "Bool" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "signature", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 64, + "kind": "Float" + }, + "kind": "named" + } + ] + } + }, + { + "description": { + "title": "alpha.inlined.endorsement_mempool.contents" + }, + "encoding": { + "tag_size": "Uint8", + "kind": { + "size": 43, + "kind": "Float" + }, + "cases": [ + { + "tag": 21, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "slot", + "layout": { + "size": "Uint16", + "kind": "Int" + }, + "data_kind": { + "size": 2, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "level", + "layout": { + "size": "Int32", + "kind": "Int" + }, + "data_kind": { + "size": 4, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "round", + "layout": { + "size": "Int32", + "kind": "Int" + }, + "data_kind": { + "size": 4, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "block_payload_hash", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 32, + "kind": "Float" + }, + "kind": "named" + } + ], + "name": "Endorsement" + } + ] + } + }, + { + "description": { + "title": "alpha.inlined.endorsement" + }, + "encoding": { + "fields": [ + { + "name": "branch", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 32, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "operations", + "layout": { + "name": "alpha.inlined.endorsement_mempool.contents", + "kind": "Ref" + }, + "data_kind": { + "size": 43, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "signature", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "kind": "Variable" + }, + "kind": "named" + } + ] + } + }, + { + "description": { + "title": "alpha.operation.alpha.contents" + }, + "encoding": { + "tag_size": "Uint8", + "kind": { + "kind": "Dynamic" + }, + "cases": [ + { + "tag": 1, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "level", + "layout": { + "size": "Int32", + "kind": "Int" + }, + "data_kind": { + "size": 4, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "nonce", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 32, + "kind": "Float" + }, + "kind": "named" + } + ], + "name": "Seed_nonce_revelation" + }, + { + "tag": 2, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "op1", + "layout": { + "name": "alpha.inlined.endorsement", + "kind": "Ref" + }, + "data_kind": { + "kind": "Variable" + }, + "kind": "named" + }, + { + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "op2", + "layout": { + "name": "alpha.inlined.endorsement", + "kind": "Ref" + }, + "data_kind": { + "kind": "Variable" + }, + "kind": "named" + } + ], + "name": "Double_endorsement_evidence" + }, + { + "tag": 3, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "bh1", + "layout": { + "name": "alpha.block_header.alpha.full_header", + "kind": "Ref" + }, + "data_kind": { + "kind": "Dynamic" + }, + "kind": "named" + }, + { + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "bh2", + "layout": { + "name": "alpha.block_header.alpha.full_header", + "kind": "Ref" + }, + "data_kind": { + "kind": "Dynamic" + }, + "kind": "named" + } + ], + "name": "Double_baking_evidence" + }, + { + "tag": 4, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "pkh", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 20, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "secret", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 20, + "kind": "Float" + }, + "kind": "named" + } + ], + "name": "Activate_account" + }, + { + "tag": 5, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "source", + "layout": { + "name": "public_key_hash", + "kind": "Ref" + }, + "data_kind": { + "size": 21, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "period", + "layout": { + "size": "Int32", + "kind": "Int" + }, + "data_kind": { + "size": 4, + "kind": "Float" + }, + "kind": "named" + }, + { + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "proposals", + "layout": { + "layout": { + "kind": "Bytes" + }, + "kind": "Seq" + }, + "data_kind": { + "kind": "Variable" + }, + "kind": "named" + } + ], + "name": "Proposals" + }, + { + "tag": 6, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "source", + "layout": { + "name": "public_key_hash", + "kind": "Ref" + }, + "data_kind": { + "size": 21, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "period", + "layout": { + "size": "Int32", + "kind": "Int" + }, + "data_kind": { + "size": 4, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "proposal", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 32, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "ballot", + "layout": { + "size": "Int8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" + } + ], + "name": "Ballot" + }, + { + "tag": 7, "fields": [ { "name": "Tag", @@ -3237,112 +4519,75 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "slot", + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "op1", "layout": { - "size": "Uint16", - "kind": "Int" + "name": "alpha.inlined.preendorsement", + "kind": "Ref" }, "data_kind": { - "size": 2, - "kind": "Float" + "kind": "Variable" }, "kind": "named" }, { - "name": "level", + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "op2", "layout": { - "size": "Int32", - "kind": "Int" + "name": "alpha.inlined.preendorsement", + "kind": "Ref" }, "data_kind": { - "size": 4, - "kind": "Float" + "kind": "Variable" }, "kind": "named" - }, + } + ], + "name": "Double_preendorsement_evidence" + }, + { + "tag": 17, + "fields": [ { - "name": "round", + "name": "Tag", "layout": { - "size": "Int32", + "size": "Uint8", "kind": "Int" }, "data_kind": { - "size": 4, + "size": 1, "kind": "Float" }, "kind": "named" }, { - "name": "block_payload_hash", + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "arbitrary", "layout": { - "kind": "Bytes" + "kind": "String" }, "data_kind": { - "size": 32, - "kind": "Float" + "kind": "Variable" }, "kind": "named" } ], - "name": "Endorsement" - } - ] - } - }, - { - "description": { - "title": "alpha.inlined.endorsement" - }, - "encoding": { - "fields": [ - { - "name": "branch", - "layout": { - "kind": "Bytes" - }, - "data_kind": { - "size": 32, - "kind": "Float" - }, - "kind": "named" - }, - { - "name": "operations", - "layout": { - "name": "alpha.inlined.endorsement_mempool.contents", - "kind": "Ref" - }, - "data_kind": { - "size": 43, - "kind": "Float" - }, - "kind": "named" + "name": "Failing_noop" }, { - "name": "signature", - "layout": { - "kind": "Bytes" - }, - "data_kind": { - "kind": "Variable" - }, - "kind": "named" - } - ] - } - }, - { - "description": { - "title": "alpha.operation.alpha.contents" - }, - "encoding": { - "tag_size": "Uint8", - "kind": { - "kind": "Dynamic" - }, - "cases": [ - { - "tag": 1, + "tag": 20, "fields": [ { "name": "Tag", @@ -3356,6 +4601,18 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' }, "kind": "named" }, + { + "name": "slot", + "layout": { + "size": "Uint16", + "kind": "Int" + }, + "data_kind": { + "size": 2, + "kind": "Float" + }, + "kind": "named" + }, { "name": "level", "layout": { @@ -3369,7 +4626,19 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "nonce", + "name": "round", + "layout": { + "size": "Int32", + "kind": "Int" + }, + "data_kind": { + "size": 4, + "kind": "Float" + }, + "kind": "named" + }, + { + "name": "block_payload_hash", "layout": { "kind": "Bytes" }, @@ -3380,10 +4649,10 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" } ], - "name": "Seed_nonce_revelation" + "name": "Preendorsement" }, { - "tag": 2, + "tag": 21, "fields": [ { "name": "Tag", @@ -3398,42 +4667,57 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "kind": "dyn", - "num_fields": 1, - "size": "Uint30" + "name": "slot", + "layout": { + "size": "Uint16", + "kind": "Int" + }, + "data_kind": { + "size": 2, + "kind": "Float" + }, + "kind": "named" }, { - "name": "op1", + "name": "level", "layout": { - "name": "alpha.inlined.endorsement", - "kind": "Ref" + "size": "Int32", + "kind": "Int" }, "data_kind": { - "kind": "Variable" + "size": 4, + "kind": "Float" }, "kind": "named" }, { - "kind": "dyn", - "num_fields": 1, - "size": "Uint30" + "name": "round", + "layout": { + "size": "Int32", + "kind": "Int" + }, + "data_kind": { + "size": 4, + "kind": "Float" + }, + "kind": "named" }, { - "name": "op2", + "name": "block_payload_hash", "layout": { - "name": "alpha.inlined.endorsement", - "kind": "Ref" + "kind": "Bytes" }, "data_kind": { - "kind": "Variable" + "size": 32, + "kind": "Float" }, "kind": "named" } ], - "name": "Double_endorsement_evidence" + "name": "Endorsement" }, { - "tag": 3, + "tag": 107, "fields": [ { "name": "Tag", @@ -3448,14 +4732,21 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "kind": "dyn", - "num_fields": 1, - "size": "Uint30" + "name": "source", + "layout": { + "name": "public_key_hash", + "kind": "Ref" + }, + "data_kind": { + "size": 21, + "kind": "Float" + }, + "kind": "named" }, { - "name": "bh1", + "name": "fee", "layout": { - "name": "alpha.block_header.alpha.full_header", + "name": "N.t", "kind": "Ref" }, "data_kind": { @@ -3464,66 +4755,54 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "kind": "dyn", - "num_fields": 1, - "size": "Uint30" - }, - { - "name": "bh2", + "name": "counter", "layout": { - "name": "alpha.block_header.alpha.full_header", + "name": "N.t", "kind": "Ref" }, "data_kind": { "kind": "Dynamic" }, - "kind": "named" - } - ], - "name": "Double_baking_evidence" - }, - { - "tag": 4, - "fields": [ + "kind": "named" + }, { - "name": "Tag", + "name": "gas_limit", "layout": { - "size": "Uint8", - "kind": "Int" + "name": "N.t", + "kind": "Ref" }, "data_kind": { - "size": 1, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" }, { - "name": "pkh", + "name": "storage_limit", "layout": { - "kind": "Bytes" + "name": "N.t", + "kind": "Ref" }, "data_kind": { - "size": 20, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" }, { - "name": "secret", + "name": "public_key", "layout": { - "kind": "Bytes" + "name": "public_key", + "kind": "Ref" }, "data_kind": { - "size": 20, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" } ], - "name": "Activate_account" + "name": "Reveal" }, { - "tag": 5, + "tag": 108, "fields": [ { "name": "Tag", @@ -3550,105 +4829,92 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "period", + "name": "fee", "layout": { - "size": "Int32", - "kind": "Int" + "name": "N.t", + "kind": "Ref" }, "data_kind": { - "size": 4, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" }, { - "kind": "dyn", - "num_fields": 1, - "size": "Uint30" - }, - { - "name": "proposals", + "name": "counter", "layout": { - "layout": { - "kind": "Bytes" - }, - "kind": "Seq" + "name": "N.t", + "kind": "Ref" }, "data_kind": { - "kind": "Variable" + "kind": "Dynamic" }, "kind": "named" - } - ], - "name": "Proposals" - }, - { - "tag": 6, - "fields": [ + }, { - "name": "Tag", + "name": "gas_limit", "layout": { - "size": "Uint8", - "kind": "Int" + "name": "N.t", + "kind": "Ref" }, "data_kind": { - "size": 1, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" }, { - "name": "source", + "name": "storage_limit", "layout": { - "name": "public_key_hash", + "name": "N.t", "kind": "Ref" }, "data_kind": { - "size": 21, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" }, { - "name": "period", + "name": "amount", "layout": { - "size": "Int32", - "kind": "Int" + "name": "N.t", + "kind": "Ref" }, "data_kind": { - "size": 4, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" }, { - "name": "proposal", + "name": "destination", "layout": { - "kind": "Bytes" + "name": "alpha.transaction_destination", + "kind": "Ref" }, "data_kind": { - "size": 32, + "size": 22, "kind": "Float" }, "kind": "named" }, { - "name": "ballot", + "kind": "option_indicator", + "name": "parameters" + }, + { + "name": "parameters", "layout": { - "size": "Int8", - "kind": "Int" + "name": "X_10", + "kind": "Ref" }, "data_kind": { - "size": 1, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" } ], - "name": "Ballot" + "name": "Transaction" }, { - "tag": 7, + "tag": 109, "fields": [ { "name": "Tag", @@ -3663,140 +4929,104 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "kind": "dyn", - "num_fields": 1, - "size": "Uint30" - }, - { - "name": "op1", + "name": "source", "layout": { - "name": "alpha.inlined.preendorsement", + "name": "public_key_hash", "kind": "Ref" }, "data_kind": { - "kind": "Variable" + "size": 21, + "kind": "Float" }, "kind": "named" }, { - "kind": "dyn", - "num_fields": 1, - "size": "Uint30" - }, - { - "name": "op2", + "name": "fee", "layout": { - "name": "alpha.inlined.preendorsement", + "name": "N.t", "kind": "Ref" }, "data_kind": { - "kind": "Variable" + "kind": "Dynamic" }, "kind": "named" - } - ], - "name": "Double_preendorsement_evidence" - }, - { - "tag": 17, - "fields": [ + }, { - "name": "Tag", + "name": "counter", "layout": { - "size": "Uint8", - "kind": "Int" + "name": "N.t", + "kind": "Ref" }, "data_kind": { - "size": 1, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" }, { - "kind": "dyn", - "num_fields": 1, - "size": "Uint30" - }, - { - "name": "arbitrary", + "name": "gas_limit", "layout": { - "kind": "String" + "name": "N.t", + "kind": "Ref" }, "data_kind": { - "kind": "Variable" + "kind": "Dynamic" }, "kind": "named" - } - ], - "name": "Failing_noop" - }, - { - "tag": 20, - "fields": [ + }, { - "name": "Tag", + "name": "storage_limit", "layout": { - "size": "Uint8", - "kind": "Int" + "name": "N.t", + "kind": "Ref" }, "data_kind": { - "size": 1, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" }, { - "name": "slot", + "name": "balance", "layout": { - "size": "Uint16", - "kind": "Int" + "name": "N.t", + "kind": "Ref" }, "data_kind": { - "size": 2, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" }, { - "name": "level", - "layout": { - "size": "Int32", - "kind": "Int" - }, - "data_kind": { - "size": 4, - "kind": "Float" - }, - "kind": "named" + "kind": "option_indicator", + "name": "delegate" }, { - "name": "round", + "name": "delegate", "layout": { - "size": "Int32", - "kind": "Int" + "name": "public_key_hash", + "kind": "Ref" }, "data_kind": { - "size": 4, + "size": 21, "kind": "Float" }, "kind": "named" }, { - "name": "block_payload_hash", + "name": "script", "layout": { - "kind": "Bytes" + "name": "alpha.scripted.contracts", + "kind": "Ref" }, "data_kind": { - "size": 32, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" } ], - "name": "Preendorsement" + "name": "Origination" }, { - "tag": 21, + "tag": 110, "fields": [ { "name": "Tag", @@ -3811,57 +5041,82 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "slot", + "name": "source", "layout": { - "size": "Uint16", - "kind": "Int" + "name": "public_key_hash", + "kind": "Ref" }, "data_kind": { - "size": 2, + "size": 21, "kind": "Float" }, "kind": "named" }, { - "name": "level", + "name": "fee", "layout": { - "size": "Int32", - "kind": "Int" + "name": "N.t", + "kind": "Ref" + }, + "data_kind": { + "kind": "Dynamic" + }, + "kind": "named" + }, + { + "name": "counter", + "layout": { + "name": "N.t", + "kind": "Ref" + }, + "data_kind": { + "kind": "Dynamic" + }, + "kind": "named" + }, + { + "name": "gas_limit", + "layout": { + "name": "N.t", + "kind": "Ref" }, "data_kind": { - "size": 4, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" }, { - "name": "round", + "name": "storage_limit", "layout": { - "size": "Int32", - "kind": "Int" + "name": "N.t", + "kind": "Ref" }, "data_kind": { - "size": 4, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" }, { - "name": "block_payload_hash", + "kind": "option_indicator", + "name": "delegate" + }, + { + "name": "delegate", "layout": { - "kind": "Bytes" + "name": "public_key_hash", + "kind": "Ref" }, "data_kind": { - "size": 32, + "size": 21, "kind": "Float" }, "kind": "named" } ], - "name": "Endorsement" + "name": "Delegation" }, { - "tag": 107, + "tag": 111, "fields": [ { "name": "Tag", @@ -3932,21 +5187,25 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "public_key", + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" + }, + { + "name": "value", "layout": { - "name": "public_key", - "kind": "Ref" + "kind": "Bytes" }, "data_kind": { - "kind": "Dynamic" + "kind": "Variable" }, "kind": "named" } ], - "name": "Reveal" + "name": "Register_global_constant" }, { - "tag": 108, + "tag": 112, "fields": [ { "name": "Tag", @@ -4017,7 +5276,11 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "amount", + "kind": "option_indicator", + "name": "limit" + }, + { + "name": "limit", "layout": { "name": "N.t", "kind": "Ref" @@ -4026,27 +5289,74 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "Dynamic" }, "kind": "named" + } + ], + "name": "Set_deposits_limit" + }, + { + "tag": 150, + "fields": [ + { + "name": "Tag", + "layout": { + "size": "Uint8", + "kind": "Int" + }, + "data_kind": { + "size": 1, + "kind": "Float" + }, + "kind": "named" }, { - "name": "destination", + "name": "source", "layout": { - "name": "alpha.transaction_destination", + "name": "public_key_hash", "kind": "Ref" }, "data_kind": { - "size": 22, + "size": 21, "kind": "Float" }, "kind": "named" }, { - "kind": "option_indicator", - "name": "parameters" + "name": "fee", + "layout": { + "name": "N.t", + "kind": "Ref" + }, + "data_kind": { + "kind": "Dynamic" + }, + "kind": "named" }, { - "name": "parameters", + "name": "counter", "layout": { - "name": "X_3", + "name": "N.t", + "kind": "Ref" + }, + "data_kind": { + "kind": "Dynamic" + }, + "kind": "named" + }, + { + "name": "gas_limit", + "layout": { + "name": "N.t", + "kind": "Ref" + }, + "data_kind": { + "kind": "Dynamic" + }, + "kind": "named" + }, + { + "name": "storage_limit", + "layout": { + "name": "N.t", "kind": "Ref" }, "data_kind": { @@ -4055,10 +5365,10 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" } ], - "name": "Transaction" + "name": "Tx_rollup_origination" }, { - "tag": 109, + "tag": 151, "fields": [ { "name": "Tag", @@ -4129,48 +5439,36 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "balance", + "name": "rollup", "layout": { - "name": "N.t", - "kind": "Ref" + "kind": "Bytes" }, "data_kind": { - "kind": "Dynamic" + "size": 20, + "kind": "Float" }, "kind": "named" }, { - "kind": "option_indicator", - "name": "delegate" - }, - { - "name": "delegate", - "layout": { - "name": "public_key_hash", - "kind": "Ref" - }, - "data_kind": { - "size": 21, - "kind": "Float" - }, - "kind": "named" + "kind": "dyn", + "num_fields": 1, + "size": "Uint30" }, { - "name": "script", + "name": "content", "layout": { - "name": "alpha.scripted.contracts", - "kind": "Ref" + "kind": "String" }, "data_kind": { - "kind": "Dynamic" + "kind": "Variable" }, "kind": "named" } ], - "name": "Origination" + "name": "Tx_rollup_submit_batch" }, { - "tag": 110, + "tag": 152, "fields": [ { "name": "Tag", @@ -4241,26 +5539,32 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "kind": "option_indicator", - "name": "delegate" + "name": "rollup", + "layout": { + "kind": "Bytes" + }, + "data_kind": { + "size": 20, + "kind": "Float" + }, + "kind": "named" }, { - "name": "delegate", + "name": "commitment", "layout": { - "name": "public_key_hash", + "name": "X_6", "kind": "Ref" }, "data_kind": { - "size": 21, - "kind": "Float" + "kind": "Dynamic" }, "kind": "named" } ], - "name": "Delegation" + "name": "Tx_rollup_commit" }, { - "tag": 111, + "tag": 153, "fields": [ { "name": "Tag", @@ -4331,25 +5635,21 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "kind": "dyn", - "num_fields": 1, - "size": "Uint30" - }, - { - "name": "value", + "name": "rollup", "layout": { "kind": "Bytes" }, "data_kind": { - "kind": "Variable" + "size": 20, + "kind": "Float" }, "kind": "named" } ], - "name": "Register_global_constant" + "name": "Tx_rollup_return_bond" }, { - "tag": 112, + "tag": 154, "fields": [ { "name": "Tag", @@ -4420,76 +5720,56 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "kind": "option_indicator", - "name": "limit" - }, - { - "name": "limit", - "layout": { - "name": "N.t", - "kind": "Ref" - }, - "data_kind": { - "kind": "Dynamic" - }, - "kind": "named" - } - ], - "name": "Set_deposits_limit" - }, - { - "tag": 150, - "fields": [ - { - "name": "Tag", + "name": "rollup", "layout": { - "size": "Uint8", - "kind": "Int" + "kind": "Bytes" }, "data_kind": { - "size": 1, + "size": 20, "kind": "Float" }, "kind": "named" }, { - "name": "source", + "name": "level", "layout": { - "name": "public_key_hash", - "kind": "Ref" + "size": "Int32", + "kind": "Int" }, "data_kind": { - "size": 21, + "size": 4, "kind": "Float" }, "kind": "named" }, { - "name": "fee", + "name": "hash", "layout": { - "name": "N.t", - "kind": "Ref" + "kind": "Bytes" }, "data_kind": { - "kind": "Dynamic" + "size": 32, + "kind": "Float" }, "kind": "named" }, { - "name": "counter", + "name": "batch_index", "layout": { - "name": "N.t", - "kind": "Ref" + "min": -1073741824, + "max": 1073741823, + "kind": "RangedInt" }, "data_kind": { - "kind": "Dynamic" + "size": 4, + "kind": "Float" }, "kind": "named" }, { - "name": "gas_limit", + "name": "batch", "layout": { - "name": "N.t", + "name": "X_5", "kind": "Ref" }, "data_kind": { @@ -4498,21 +5778,22 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "storage_limit", + "name": "nonce", "layout": { - "name": "N.t", - "kind": "Ref" + "size": "Int64", + "kind": "Int" }, "data_kind": { - "kind": "Dynamic" + "size": 8, + "kind": "Float" }, "kind": "named" } ], - "name": "Tx_rollup_origination" + "name": "Tx_rollup_rejection" }, { - "tag": 151, + "tag": 155, "fields": [ { "name": "Tag", @@ -4583,33 +5864,18 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "kind": "named" }, { - "name": "rollup", - "layout": { - "kind": "Bytes" - }, - "data_kind": { - "size": 20, - "kind": "Float" - }, - "kind": "named" - }, - { - "kind": "dyn", - "num_fields": 1, - "size": "Uint30" - }, - { - "name": "content", + "name": "hash", "layout": { - "kind": "String" + "kind": "Bytes" }, "data_kind": { - "kind": "Variable" + "size": 20, + "kind": "Float" }, "kind": "named" } ], - "name": "Tx_rollup_submit_batch" + "name": "Tx_rollup_prerejection" }, { "tag": 200, @@ -5473,6 +6739,10 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' } ], "definitions": { + "Commitment_hash": { + "title": "A commitment ID (Base58Check-encoded)", + "$ref": "#/definitions/unistring" + }, "Context_hash": { "title": "A hash of context (Base58Check-encoded)", "$ref": "#/definitions/unistring" @@ -5493,6 +6763,10 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "title": "A Tezos protocol ID (Base58Check-encoded)", "$ref": "#/definitions/unistring" }, + "Rejection_hash": { + "title": "A rejection ID (Base58Check-encoded)", + "$ref": "#/definitions/unistring" + }, "Signature": { "title": "A Ed25519, Secp256k1 or P256 signature (Base58Check-encoded)", "$ref": "#/definitions/unistring" @@ -5505,6 +6779,10 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "title": "A Ed25519, Secp256k1, or P256 public key hash (Base58Check-encoded)", "$ref": "#/definitions/unistring" }, + "Tx_rollup_l2_address": { + "title": "The hash of a BLS public key used to identify a L2 ticket holders (Base58Check-encoded)", + "$ref": "#/definitions/unistring" + }, "alpha.block_header.alpha.full_header": { "title": "Shell header", "description": "Block header's shell-related content. It contains information such as the block level, its predecessor and timestamp.", @@ -5579,6 +6857,11 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' ], "additionalProperties": false }, + "alpha.contract_id": { + "title": "A contract handle", + "description": "A contract notation as given to an RPC or inside scripts. Can be a base58 implicit contract hash or a base58 originated contract hash.", + "$ref": "#/definitions/unistring" + }, "alpha.entrypoint": { "title": "entrypoint", "description": "Named entrypoint to a Michelson smart contract", @@ -5758,14 +7041,14 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "False", "DUG", "DIG", - "chest_key", + "ticket", "BLAKE2B", "list", - "bls12_381_g1", + "never", "Pair", "INT", "nat", - "never", + "chain_id", "storage", "SIZE", "view", @@ -5782,15 +7065,15 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "operation", "MAP", "option", - "bls12_381_fr", + "bls12_381_g2", "ADD", "IMPLICIT_ACCOUNT", "SHA512", "int", "LSL", - "bls12_381_g2", - "ticket", - "sapling_transaction", + "bls12_381_g1", + "bls12_381_fr", + "tx_rollup_l2_address", "COMPARE", "SWAP", "STEPS_TO_QUOTA", @@ -5798,6 +7081,7 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "pair", "BALANCE", "CONCAT", + "constant", "MUL", "FAILWITH", "Elt", @@ -5856,7 +7140,7 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "PACK", "IF_CONS", "KECCAK", - "chest", + "chest_key", "UNIT", "EMPTY_SET", "NEQ", @@ -5868,7 +7152,7 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "contract", "LSR", "EMPTY_BIG_MAP", - "sapling_state", + "sapling_transaction", "JOIN_TICKETS", "LEVEL", "UNPAIR", @@ -5876,8 +7160,8 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "PUSH", "big_map", "GT", - "chain_id", - "constant", + "sapling_state", + "chest", "NOW", "IF_NONE", "PAIR", @@ -6693,6 +7977,314 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' ], "additionalProperties": false }, + { + "title": "Tx_rollup_commit", + "type": "object", + "properties": { + "kind": { + "type": "string", + "enum": [ + "tx_rollup_commit" + ] + }, + "source": { + "$ref": "#/definitions/Signature.Public_key_hash" + }, + "fee": { + "$ref": "#/definitions/alpha.mutez" + }, + "counter": { + "$ref": "#/definitions/positive_bignum" + }, + "gas_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "storage_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "rollup": { + "$ref": "#/definitions/alpha.tx_rollup_id" + }, + "commitment": { + "type": "object", + "properties": { + "level": { + "type": "integer", + "minimum": -2147483648, + "maximum": 2147483647 + }, + "batches": { + "type": "array", + "items": { + "type": "object", + "properties": { + "effects": { + "type": "array", + "items": { + "type": "object", + "properties": { + "contract": { + "$ref": "#/definitions/alpha.contract_id" + }, + "ticket": { + "$ref": "#/definitions/script_expr" + }, + "amount": { + "$ref": "#/definitions/int64" + } + }, + "required": [ + "amount", + "ticket", + "contract" + ], + "additionalProperties": false + } + }, + "root": { + "type": "string", + "pattern": "^([a-zA-Z0-9][a-zA-Z0-9])*$" + } + }, + "required": [ + "root", + "effects" + ], + "additionalProperties": false + } + }, + "predecessor": { + "oneOf": [ + { + "title": "Some", + "$ref": "#/definitions/Commitment_hash" + }, + { + "title": "None", + "type": "null" + } + ] + } + }, + "required": [ + "predecessor", + "batches", + "level" + ], + "additionalProperties": false + } + }, + "required": [ + "commitment", + "rollup", + "storage_limit", + "gas_limit", + "counter", + "fee", + "source", + "kind" + ], + "additionalProperties": false + }, + { + "title": "Tx_rollup_return_bond", + "type": "object", + "properties": { + "kind": { + "type": "string", + "enum": [ + "tx_rollup_return_bond" + ] + }, + "source": { + "$ref": "#/definitions/Signature.Public_key_hash" + }, + "fee": { + "$ref": "#/definitions/alpha.mutez" + }, + "counter": { + "$ref": "#/definitions/positive_bignum" + }, + "gas_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "storage_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "rollup": { + "$ref": "#/definitions/alpha.tx_rollup_id" + } + }, + "required": [ + "rollup", + "storage_limit", + "gas_limit", + "counter", + "fee", + "source", + "kind" + ], + "additionalProperties": false + }, + { + "title": "Tx_rollup_rejection", + "type": "object", + "properties": { + "kind": { + "type": "string", + "enum": [ + "tx_rollup_rejection" + ] + }, + "source": { + "$ref": "#/definitions/Signature.Public_key_hash" + }, + "fee": { + "$ref": "#/definitions/alpha.mutez" + }, + "counter": { + "$ref": "#/definitions/positive_bignum" + }, + "gas_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "storage_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "rollup": { + "$ref": "#/definitions/alpha.tx_rollup_id" + }, + "level": { + "type": "integer", + "minimum": -2147483648, + "maximum": 2147483647 + }, + "hash": { + "$ref": "#/definitions/Commitment_hash" + }, + "batch_index": { + "type": "integer", + "minimum": -1073741824, + "maximum": 1073741823 + }, + "batch": { + "oneOf": [ + { + "title": "Batch", + "type": "object", + "properties": { + "batch": { + "$ref": "#/definitions/unistring" + } + }, + "required": [ + "batch" + ], + "additionalProperties": false + }, + { + "title": "Deposit", + "type": "object", + "properties": { + "deposit": { + "type": "object", + "properties": { + "destination": { + "oneOf": [ + { + "title": "Key", + "type": "integer", + "minimum": -2147483648, + "maximum": 2147483647 + }, + { + "title": "Value", + "$ref": "#/definitions/Tx_rollup_l2_address" + } + ] + }, + "ticket_hash": { + "$ref": "#/definitions/script_expr" + }, + "amount": { + "$ref": "#/definitions/int64" + } + }, + "required": [ + "amount", + "ticket_hash", + "destination" + ], + "additionalProperties": false + } + }, + "required": [ + "deposit" + ], + "additionalProperties": false + } + ] + }, + "nonce": { + "$ref": "#/definitions/int64" + } + }, + "required": [ + "nonce", + "batch", + "batch_index", + "hash", + "level", + "rollup", + "storage_limit", + "gas_limit", + "counter", + "fee", + "source", + "kind" + ], + "additionalProperties": false + }, + { + "title": "Tx_rollup_prerejection", + "type": "object", + "properties": { + "kind": { + "type": "string", + "enum": [ + "tx_rollup_prerejection" + ] + }, + "source": { + "$ref": "#/definitions/Signature.Public_key_hash" + }, + "fee": { + "$ref": "#/definitions/alpha.mutez" + }, + "counter": { + "$ref": "#/definitions/positive_bignum" + }, + "gas_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "storage_limit": { + "$ref": "#/definitions/positive_bignum" + }, + "hash": { + "$ref": "#/definitions/Rejection_hash" + } + }, + "required": [ + "hash", + "storage_limit", + "gas_limit", + "counter", + "fee", + "source", + "kind" + ], + "additionalProperties": false + }, { "title": "Sc_rollup_originate", "type": "object", @@ -6961,7 +8553,7 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' }, "alpha.transaction_destination": { "title": "A destination of a transaction", - "description": "A destination notation compatible with the contract notation as given to an RPC or inside scripts. Can be a base58 implicit contract hash or a base58 originated contract hash.", + "description": "A destination notation compatible with the contract notation as given to an RPC or inside scripts. Can be a base58 implicit contract hash, a base58 originated contract hash, or a base58 originated transaction rollup.", "$ref": "#/definitions/unistring" }, "alpha.tx_rollup_id": { @@ -6994,6 +8586,11 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "pattern": "^([a-zA-Z0-9][a-zA-Z0-9])*$" } }, + "int64": { + "title": "64 bit integers", + "description": "Decimal representation of 64 bit integers", + "type": "string" + }, "micheline.alpha.michelson_v1.expression": { "oneOf": [ { @@ -7107,6 +8704,10 @@ curl -s 'http://localhost:[PORT]/describe/chains/main/mempool?recurse=yes' "description": "Decimal representation of a positive big number", "type": "string" }, + "script_expr": { + "title": "A script expression ID (Base58Check-encoded)", + "$ref": "#/definitions/unistring" + }, "timestamp.protocol": { "description": "A timestamp as seen by the protocol: second-level precision, epoch based.", "$ref": "#/definitions/unistring" diff --git a/tezt/_regressions/rpc/alpha.proxy.others.out b/tezt/_regressions/rpc/alpha.proxy.others.out index 760067d3046d4c8f3794c8cee1c636c586c33a79..65e3efa2f3f680a1e364dcc9140eb874f70ca382 100644 --- a/tezt/_regressions/rpc/alpha.proxy.others.out +++ b/tezt/_regressions/rpc/alpha.proxy.others.out @@ -32,7 +32,8 @@ protocol of proxy unspecified, using the node's protocol: ProtoGenesisGenesisGen "cache_stake_distribution_cycles": 8, "cache_sampler_state_cycles": 8, "tx_rollup_enable": false, "tx_rollup_origination_size": 60000, "tx_rollup_hard_size_limit_per_inbox": 100000, - "tx_rollup_hard_size_limit_per_message": 5000, "sc_rollup_enable": false, + "tx_rollup_hard_size_limit_per_message": 5000, + "tx_rollup_commitment_bond": "10000000000", "sc_rollup_enable": false, "sc_rollup_origination_size": 6314 } ./tezos-client --mode proxy rpc get /chains/main/blocks/head/helpers/baking_rights diff --git a/tezt/_regressions/rpc/alpha.proxy_server.others.out b/tezt/_regressions/rpc/alpha.proxy_server.others.out index 6ec3dc57ad9568e2a39b9d58f8e0967a5d66274c..70f5d0b24b36935a730325054b6eeeada8963f04 100644 --- a/tezt/_regressions/rpc/alpha.proxy_server.others.out +++ b/tezt/_regressions/rpc/alpha.proxy_server.others.out @@ -31,7 +31,8 @@ tezt/_regressions/rpc/alpha.proxy_server.others.out "cache_stake_distribution_cycles": 8, "cache_sampler_state_cycles": 8, "tx_rollup_enable": false, "tx_rollup_origination_size": 60000, "tx_rollup_hard_size_limit_per_inbox": 100000, - "tx_rollup_hard_size_limit_per_message": 5000, "sc_rollup_enable": false, + "tx_rollup_hard_size_limit_per_message": 5000, + "tx_rollup_commitment_bond": "10000000000", "sc_rollup_enable": false, "sc_rollup_origination_size": 6314 } ./tezos-client rpc get /chains/main/blocks/head/helpers/baking_rights diff --git a/tezt/_regressions/tx_rollup_deposit.out b/tezt/_regressions/tx_rollup_deposit.out new file mode 100644 index 0000000000000000000000000000000000000000..9c4cf63c5cd237351d1a65982f40cf7f1f71efdd --- /dev/null +++ b/tezt/_regressions/tx_rollup_deposit.out @@ -0,0 +1,67 @@ +tezt/_regressions/tx_rollup_deposit.out + +./tezos-client --wait none originate contract tx_rollup_deposit transferring 0 from '[PUBLIC_KEY_HASH]' running file:./tezt/tests/contracts/proto_alpha/tx_rollup_deposit.tz --init Unit --burn-cap 3 +Node is bootstrapped. +Estimated gas: 1423.597 units (will add 100 for safety) +Estimated storage: 399 bytes added (will add 20 for safety) +Operation successfully injected in the node. +Operation hash is 'oo15dEUae4oEBWg2x3ReiPVJu5kAcRfUA5xPPGccLBPz3G4rN2i' +NOT waiting for the operation to be included. +Use command + tezos-client wait for oo15dEUae4oEBWg2x3ReiPVJu5kAcRfUA5xPPGccLBPz3G4rN2i to be included --confirmations 1 --branch BLockGenesisGenesisGenesisGenesisGenesisf79b5d1CoW2 +and/or an external block explorer to make sure that it has been included. +This sequence of operations was run: + Manager signed operations: + From: [PUBLIC_KEY_HASH] + Fee to the baker: ꜩ0.000522 + Expected counter: 1 + Gas limit: 1524 + Storage limit: 419 bytes + Balance updates: + [PUBLIC_KEY_HASH] ... -ꜩ0.000522 + payload fees(the block proposer) ....... +ꜩ0.000522 + Origination: + From: [PUBLIC_KEY_HASH] + Credit: ꜩ0 + Script: + { parameter (pair address tx_rollup_l2_address) ; + storage unit ; + code { CAR ; + UNPAIR ; + CONTRACT %deposit (pair (ticket unit) tx_rollup_l2_address) ; + IF_SOME + { SWAP ; + PUSH mutez 0 ; + SWAP ; + PUSH nat 10 ; + PUSH unit Unit ; + TICKET ; + PAIR ; + TRANSFER_TOKENS ; + DIP { NIL operation } ; + CONS ; + DIP { PUSH unit Unit } ; + PAIR } + { FAIL } } } + Initial storage: Unit + No delegate for this contract + This origination was successfully applied + Originated contracts: + [CONTRACT_HASH] + Storage size: 142 bytes + Paid storage size diff: 142 bytes + Consumed gas: 1423.597 + Balance updates: + [PUBLIC_KEY_HASH] ... -ꜩ0.0355 + storage fees ........................... +ꜩ0.0355 + [PUBLIC_KEY_HASH] ... -ꜩ0.06425 + storage fees ........................... +ꜩ0.06425 + +New contract [CONTRACT_HASH] originated. +Contract memorized as tx_rollup_deposit. +KT1TCZHxqrmEpwDV8mB1Yvu8Bx5PHvLpDbSy +tru1HyCWUoe7VYrjsqRaBTzU7R5zcKdJqnmiK + +./tezos-client rpc get /chains/main/blocks/head/context/tx_rollup/tru1HyCWUoe7VYrjsqRaBTzU7R5zcKdJqnmiK/inbox +{ "contents": [ "M3EbXfD56vVzukcEsQ8vdag3szduGoxZcD3jGwNjVKqSiKWhRZG" ], + "cumulated_size": 45 } diff --git a/tezt/_regressions/tx_rollup_simple_use_case.out b/tezt/_regressions/tx_rollup_simple_use_case.out index cb96534eb5b9d6f74187ce63bc8c9dd9148efa3e..d8f7f13f6dcc8945b068c7aeb70366d8ad2e6496 100644 --- a/tezt/_regressions/tx_rollup_simple_use_case.out +++ b/tezt/_regressions/tx_rollup_simple_use_case.out @@ -2,11 +2,12 @@ tezt/_regressions/tx_rollup_simple_use_case.out tru1EL3YqhLS3kwni3ikbqMrui61fA5k7StHz ./tezos-client rpc get /chains/main/blocks/head/context/tx_rollup/tru1EL3YqhLS3kwni3ikbqMrui61fA5k7StHz/state -{ "last_inbox_level": null, "fees_per_byte": "0" } +{ "first_unfinalized_level": null, "unfinalized_level_count": 0, + "fees_per_byte": "0", "last_inbox_level": null } ./tezos-client --wait none submit tx rollup batch 74657a6f73 to tru1EL3YqhLS3kwni3ikbqMrui61fA5k7StHz from '[PUBLIC_KEY_HASH]' Node is bootstrapped. -Estimated gas: 2440.196 units (will add 100 for safety) +Estimated gas: 3280.266 units (will add 100 for safety) Estimated storage: no bytes added Operation successfully injected in the node. Operation hash is '[OPERATION_HASH]' @@ -17,18 +18,18 @@ and/or an external block explorer to make sure that it has been included. This sequence of operations was run: Manager signed operations: From: [PUBLIC_KEY_HASH] - Fee to the baker: ꜩ0.000508 + Fee to the baker: ꜩ0.000592 Expected counter: 2 - Gas limit: 2541 + Gas limit: 3381 Storage limit: 0 bytes Balance updates: - [PUBLIC_KEY_HASH] ... -ꜩ0.000508 - payload fees(the block proposer) ....... +ꜩ0.000508 + [PUBLIC_KEY_HASH] ... -ꜩ0.000592 + payload fees(the block proposer) ....... +ꜩ0.000592 Tx rollup transaction:tru1EL3YqhLS3kwni3ikbqMrui61fA5k7StHz, 5 bytes, From: [PUBLIC_KEY_HASH] This tx rollup submit operation was successfully applied Balance updates: - Consumed gas: 2440.196 + Consumed gas: 3280.266 ./tezos-client rpc get /chains/main/blocks/head/context/tx_rollup/tru1EL3YqhLS3kwni3ikbqMrui61fA5k7StHz/inbox diff --git a/tezt/lib_tezos/RPC.ml b/tezt/lib_tezos/RPC.ml index 059544bcc12c457a0e4fbeee2f10bdc6582ee1e1..dbf799e1691f03ac2949aba84d2217e70b9ecb1c 100644 --- a/tezt/lib_tezos/RPC.ml +++ b/tezt/lib_tezos/RPC.ml @@ -650,6 +650,11 @@ module Tx_rollup = struct let spawn_get_inbox ?endpoint ?hooks ?chain ?block ~tx_rollup client = let path = sub_path ?chain ?block ~tx_rollup "inbox" in Client.spawn_rpc ?endpoint ?hooks GET path client + + let get_commitments ?endpoint ?hooks ?(chain = "main") ?(block = "head") + ~tx_rollup client = + let path = sub_path ~chain ~block ~tx_rollup "commitments" in + Client.rpc ?endpoint ?hooks GET path client end module Sc_rollup = struct diff --git a/tezt/lib_tezos/RPC.mli b/tezt/lib_tezos/RPC.mli index b9e3617401579b4417ba249c667089196d2fb82b..ddc9a0f1167c1b6bd49a7a16a6e99151e4b16ca2 100644 --- a/tezt/lib_tezos/RPC.mli +++ b/tezt/lib_tezos/RPC.mli @@ -1009,6 +1009,16 @@ module Tx_rollup : sig tx_rollup:string -> Client.t -> Process.t + + (** Call RPC /chain/[chain]/blocks/[block]/context/[rollup_hash]/commitments *) + val get_commitments : + ?endpoint:Client.endpoint -> + ?hooks:Process.hooks -> + ?chain:string -> + ?block:string -> + tx_rollup:string -> + Client.t -> + JSON.t Lwt.t end module Sc_rollup : sig diff --git a/tezt/tests/contracts/proto_alpha/tx_rollup_deposit.tz b/tezt/tests/contracts/proto_alpha/tx_rollup_deposit.tz new file mode 100644 index 0000000000000000000000000000000000000000..7f10911746bdfcdaf2d5077b11e0ffcd982ec6b0 --- /dev/null +++ b/tezt/tests/contracts/proto_alpha/tx_rollup_deposit.tz @@ -0,0 +1,33 @@ +parameter (pair address tx_rollup_l2_address); +storage (unit); +code { + # cast the address to contract type + CAR; + UNPAIR; + CONTRACT %deposit (pair (ticket unit) tx_rollup_l2_address); + + IF_SOME { + SWAP; + + # amount for transfering + PUSH mutez 0; + SWAP; + + # create a ticket + PUSH nat 10; + PUSH unit Unit; + TICKET; + + PAIR ; + + # deposit + TRANSFER_TOKENS; + + DIP { NIL operation }; + CONS; + + DIP { PUSH unit Unit }; + PAIR; + } + { FAIL ; } + } diff --git a/tezt/tests/tx_rollup.ml b/tezt/tests/tx_rollup.ml index a464504a42ff476b681a48419238702910669e26..77ddad1bcf59d2e472e22c7732c2a0f05d764431 100644 --- a/tezt/tests/tx_rollup.ml +++ b/tezt/tests/tx_rollup.ml @@ -199,7 +199,86 @@ let test_submit_from_originated_source ~protocols = unit +(** [test_deposit] originates a transaction rollup, and a smart + contract that it uses to perform a ticket deposit to this + rollup. *) +let test_deposit ~protocols = + let open Tezt_tezos in + Protocol.register_regression_test + ~__FILE__ + ~output_file:"tx_rollup_deposit" + ~title:"Alpha: Deposit a ticket" + ~tags:["rollup"] + ~protocols + @@ fun protocol -> + let* parameter_file = + Protocol.write_parameter_file + ~base:(Either.right (protocol, None)) + [(["tx_rollup_enable"], Some "true")] + in + let* (node, client) = + Client.init_with_protocol ~parameter_file `Client ~protocol () + in + + let* tx_rollup_contract = + Client.originate_contract + ~hooks + ~alias:"tx_rollup_deposit" + ~amount:Tez.zero + ~src:Constant.bootstrap1.public_key_hash + ~prg:"file:./tezt/tests/contracts/proto_alpha/tx_rollup_deposit.tz" + ~init:"Unit" + ~burn_cap:Tez.(of_int 3) + client + in + + Regression.capture tx_rollup_contract ; + + let* () = Client.bake_for client in + let* _ = Node.wait_for_level node 2 in + + let* tx_rollup = + Client.originate_tx_rollup + ~burn_cap:Tez.(of_int 9999999) + ~storage_limit:60_000 + ~src:Constant.bootstrap2.public_key_hash + client + in + + Regression.capture tx_rollup ; + + let* () = Client.bake_for client in + + let* _ = Node.wait_for_level node 3 in + + (* We check the rollup exists by trying to fetch its state. *) + let* _state = get_state tx_rollup client in + + (* We inject a call to the smart contract *) + let* _ = + Client.transfer + ~burn_cap:Tez.(of_int 9999999) + ~amount:Tez.zero + ~giver:"bootstrap1" + ~receiver:tx_rollup_contract + ~arg:(Format.sprintf "Pair \"%s\" 3" tx_rollup) + client + in + let* () = Client.bake_for ~minimal_fees:0 client in + let* _ = Node.wait_for_level node 4 in + + (* Check that the inbox has been created for [tx_rollup]. *) + let* inbox = get_inbox ~hooks tx_rollup client in + + Check.( + (List.length inbox.contents = 1) + int + ~error_msg:"The inbox should contain one message") ; + + unit + let register ~protocols = test_submit_batch ~protocols ; test_invalid_rollup_address ~protocols ; - test_submit_from_originated_source ~protocols + test_submit_from_originated_source ~protocols ; + test_deposit ~protocols