Skip to content
9 changes: 1 addition & 8 deletions src/app/archive/lib/diff.ml
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
open Mina_block
open Core_kernel
open Mina_base
module Breadcrumb = Transition_frontier.Breadcrumb
Expand Down Expand Up @@ -101,13 +100,7 @@ module Builder = struct
let account_creation_fee =
precomputed_values.constraint_constants.account_creation_fee
in
let previous_block_state_hash =
Mina_block.header block |> Header.protocol_state
|> Mina_state.Protocol_state.previous_state_hash
in
List.map
(Staged_ledger.latest_block_accounts_created staged_ledger
~previous_block_state_hash ) ~f:(fun acct_id ->
List.map (Breadcrumb.accounts_created breadcrumb) ~f:(fun acct_id ->
(acct_id, account_creation_fee) )
in
let tokens_used =
Expand Down
7 changes: 6 additions & 1 deletion src/app/cli/src/init/test_submit_to_archive.ml
Original file line number Diff line number Diff line change
Expand Up @@ -135,12 +135,17 @@ module Block = struct
(* [create_exn] is only safe to use for initial genesis block. *)
Staged_ledger.create_exn ~constraint_constants ~ledger
in
let accounts_created =
Precomputed_values.accounts precomputed_values
|> Lazy.force
|> List.map ~f:Precomputed_values.id_of_account_record
in
[%log info] "Generating genesis breadcrumb" ;
let breadcrumb =
Frontier_base.Breadcrumb.create ~validated_transition:validated
~staged_ledger
~transition_receipt_time:(Some (Time.now ()))
~just_emitted_a_proof:false
~just_emitted_a_proof:false ~accounts_created
in
(* Block proof contained in genesis header is just a stub.
Hence we need to generate the real proof here, in order to
Expand Down
5 changes: 4 additions & 1 deletion src/app/dump_blocks/dump_blocks.ml
Original file line number Diff line number Diff line change
Expand Up @@ -91,7 +91,10 @@ let f (type a) ?parent (outputs : a codec io list) make_breadcrumb =
List.iter outputs ~f:(fun output ->
let module Enc = (val output.encoding) in
let content =
Enc.of_breadcrumb ?with_parent_statehash:parent breadcrumb
Enc.of_breadcrumb ?with_parent_statehash:parent
~accounts_created:
(Frontier_base.Breadcrumb.accounts_created breadcrumb)
breadcrumb
in
eprintf
!"Randomly generated block, %s: %s\n"
Expand Down
15 changes: 11 additions & 4 deletions src/app/dump_blocks/encoding.ml
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ type 'a content =

let append_newline s = s ^ "\n"

let block_of_breadcrumb ?with_parent_statehash breadcrumb =
let block_of_breadcrumb ?with_parent_statehash ~accounts_created:_ breadcrumb =
let open Mina_block in
let block = Frontier_base.Breadcrumb.block breadcrumb in
match with_parent_statehash with
Expand Down Expand Up @@ -37,7 +37,10 @@ module type S = sig
val name : string

val of_breadcrumb :
?with_parent_statehash:string -> Frontier_base.Breadcrumb.t -> t
?with_parent_statehash:string
-> accounts_created:Mina_base.Account_id.t list
-> Frontier_base.Breadcrumb.t
-> t

val to_string : t -> string

Expand Down Expand Up @@ -80,9 +83,12 @@ let precomputed_values = Lazy.force Precomputed_values.for_unit_tests

let constraint_constants = precomputed_values.constraint_constants

let precomputed_of_breadcrumb ?with_parent_statehash breadcrumb =
let precomputed_of_breadcrumb ?with_parent_statehash ~accounts_created
breadcrumb =
let open Frontier_base in
let block = block_of_breadcrumb ?with_parent_statehash breadcrumb in
let block =
block_of_breadcrumb ?with_parent_statehash ~accounts_created breadcrumb
in
let staged_ledger = Transition_frontier.Breadcrumb.staged_ledger breadcrumb in
let scheduled_time =
Mina_block.Stable.Latest.header block
Expand All @@ -93,6 +99,7 @@ let precomputed_of_breadcrumb ?with_parent_statehash breadcrumb =
Mina_block.Precomputed.of_block ~logger ~constraint_constants ~staged_ledger
~scheduled_time
(Breadcrumb.block_with_hash breadcrumb)
~accounts_created

module Sexp_precomputed : S with type t = Mina_block.Precomputed.t = struct
type t = Mina_block.Precomputed.t
Expand Down
7 changes: 4 additions & 3 deletions src/lib/block_producer/block_producer.ml
Original file line number Diff line number Diff line change
Expand Up @@ -291,6 +291,7 @@ let generate_next_state ~commit_id ~zkapp_cmd_limit ~constraint_constants
| Ok
( `Ledger_proof ledger_proof_opt
, `Staged_ledger transitioned_staged_ledger
, `Accounts_created _
, `Pending_coinbase_update (is_new_stack, pending_coinbase_update)
) ->
[%log internal] "Hash_new_staged_ledger" ;
Expand Down Expand Up @@ -357,7 +358,7 @@ let generate_next_state ~commit_id ~zkapp_cmd_limit ~constraint_constants
in
let ledger_proof_statement =
match ledger_proof_opt with
| Some (proof, _) ->
| Some proof ->
Ledger_proof.Cached.statement proof
| None ->
let state =
Expand All @@ -372,7 +373,7 @@ let generate_next_state ~commit_id ~zkapp_cmd_limit ~constraint_constants
in
let supply_increase =
Option.value_map ledger_proof_opt
~f:(fun (proof, _) ->
~f:(fun proof ->
(Ledger_proof.Cached.statement proof).supply_increase )
~default:Currency.Amount.Signed.zero
in
Expand Down Expand Up @@ -423,7 +424,7 @@ let generate_next_state ~commit_id ~zkapp_cmd_limit ~constraint_constants
(Consensus.Data.Block_data.prover_state block_data)
~staged_ledger_diff:(Staged_ledger_diff.forget diff)
~ledger_proof:
(Option.map ledger_proof_opt ~f:(fun (proof, _) ->
(Option.map ledger_proof_opt ~f:(fun proof ->
Ledger_proof.Cached.read_proof_from_disk proof ) ) )
in
let witness =
Expand Down
11 changes: 11 additions & 0 deletions src/lib/bootstrap_controller/bootstrap_controller.ml
Original file line number Diff line number Diff line change
Expand Up @@ -430,6 +430,17 @@ let run_cycle ~context:(module Context : CONTEXT) ~trust_system ~verifier
time_deferred
(let open Deferred.Let_syntax in
let temp_mask = Root_ledger.as_masked temp_snarked_ledger in
(* [of_scan_state_pending_coinbases_and_snarked_ledger] is called here
* to verify the scan state we received. We ignore the resulting staged
* ledger (from [temp_mask]). Later we call [Transition_frontier.load]
* which will indirectly invoke
* [of_scan_state_pending_coinbases_and_snarked_ledger_unchecked]
* repeating the same computation (except for proof verification
* which is skipped). Chain of calls:
* [Transition_frontier.load] -> .. -> [load_from_persistence_and_start]
* -> [load_full_frontier] -> [construct_staged_ledger_at_root] ->
* -> [of_scan_state_pending_coinbases_and_snarked_ledger_unchecked]
*)
let%map result =
Staged_ledger
.of_scan_state_pending_coinbases_and_snarked_ledger ~logger
Expand Down
10 changes: 2 additions & 8 deletions src/lib/mina_block/precomputed_block.ml
Original file line number Diff line number Diff line change
Expand Up @@ -100,7 +100,7 @@ end]

let of_block ~logger
~(constraint_constants : Genesis_constants.Constraint_constants.t)
~scheduled_time ~staged_ledger block_with_hash =
~scheduled_time ~staged_ledger ~accounts_created block_with_hash =
let ledger = Staged_ledger.ledger staged_ledger in
let block = With_hash.data block_with_hash in
let state_hash =
Expand Down Expand Up @@ -145,13 +145,7 @@ let of_block ~logger
] ;
let accounts_created =
let account_creation_fee = constraint_constants.account_creation_fee in
let previous_block_state_hash =
Mina_state.Protocol_state.previous_state_hash
(Header.protocol_state header)
in
List.map
(Staged_ledger.latest_block_accounts_created staged_ledger
~previous_block_state_hash ) ~f:(fun acct_id ->
List.map accounts_created ~f:(fun acct_id ->
(acct_id, account_creation_fee) )
in
let tokens_used =
Expand Down
1 change: 1 addition & 0 deletions src/lib/mina_block/precomputed_block.mli
Original file line number Diff line number Diff line change
Expand Up @@ -56,5 +56,6 @@ val of_block :
-> constraint_constants:Genesis_constants.Constraint_constants.t
-> scheduled_time:Block_time.Time.t
-> staged_ledger:Staged_ledger.t
-> accounts_created:Account_id.t list
-> (Block.t, Mina_base.State_hash.State_hashes.t) With_hash.t
-> t
6 changes: 4 additions & 2 deletions src/lib/mina_block/validation.ml
Original file line number Diff line number Diff line change
Expand Up @@ -500,6 +500,7 @@ let validate_staged_ledger_diff ?skip_staged_ledger_verification ~logger
in
let%bind.Deferred.Result ( `Ledger_proof proof_opt
, `Staged_ledger transitioned_staged_ledger
, `Accounts_created accounts_created
, `Pending_coinbase_update _ ) =
Staged_ledger.apply ?skip_verification:skip_staged_ledger_verification
~get_completed_work
Expand Down Expand Up @@ -547,7 +548,7 @@ let validate_staged_ledger_diff ?skip_staged_ledger_verification ~logger
| None ->
(*There was no proof emitted, snarked ledger hash shouldn't change*)
Protocol_state.snarked_ledger_hash parent_protocol_state
| Some (proof, _) ->
| Some proof ->
Mina_state.Snarked_ledger_state.snarked_ledger_hash
@@ Ledger_proof.Cached.statement proof
in
Expand Down Expand Up @@ -580,7 +581,8 @@ let validate_staged_ledger_diff ?skip_staged_ledger_verification ~logger
( `Just_emitted_a_proof (Option.is_some proof_opt)
, `Block_with_validation
(t, Unsafe.set_valid_staged_ledger_diff validation)
, `Staged_ledger transitioned_staged_ledger )
, `Staged_ledger transitioned_staged_ledger
, `Accounts_created accounts_created )
| Error errors ->
Error (`Invalid_staged_ledger_diff errors)

Expand Down
1 change: 1 addition & 0 deletions src/lib/mina_block/validation.mli
Original file line number Diff line number Diff line change
Expand Up @@ -378,6 +378,7 @@ val validate_staged_ledger_diff :
, 'f )
with_block ]
* [ `Staged_ledger of Staged_ledger.t ]
* [ `Accounts_created of Account_id.t list ]
, [> `Staged_ledger_application_failed of
Staged_ledger.Staged_ledger_error.t
| `Invalid_body_reference
Expand Down
5 changes: 0 additions & 5 deletions src/lib/mina_lib/mina_lib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -853,11 +853,6 @@ let most_recent_valid_transition t = t.components.most_recent_valid_block

let block_produced_bvar t = t.components.block_produced_bvar

let staged_ledger_ledger_proof t =
let open Option.Let_syntax in
let%bind sl = best_staged_ledger_opt t in
Staged_ledger.current_ledger_proof sl

let validated_transitions t = t.pipes.validated_transitions_reader

let initialization_finish_signal t = t.initialization_finish_signal
Expand Down
2 changes: 0 additions & 2 deletions src/lib/mina_lib/mina_lib.mli
Original file line number Diff line number Diff line change
Expand Up @@ -227,8 +227,6 @@ val stop_snark_worker : ?should_wait_kill:bool -> t -> unit Deferred.t
val create :
commit_id:string -> ?wallets:Secrets.Wallets.t -> Config.t -> t Deferred.t

val staged_ledger_ledger_proof : t -> Ledger_proof.Cached.t option

val transition_frontier :
t -> Transition_frontier.t option Broadcast_pipe.Reader.t

Expand Down
3 changes: 3 additions & 0 deletions src/lib/mina_lib/mina_subscriptions.ml
Original file line number Diff line number Diff line change
Expand Up @@ -144,6 +144,9 @@ let create ~logger ~constraint_constants ~wallets ~new_blocks
in
Mina_block.Precomputed.of_block ~logger
~constraint_constants ~staged_ledger ~scheduled_time
~accounts_created:
(Frontier_base.Breadcrumb.accounts_created
breadcrumb )
new_block
in
[%log debug] "Precomputed block generated in $time ms"
Expand Down
28 changes: 14 additions & 14 deletions src/lib/one_or_two/one_or_two.ml
Original file line number Diff line number Diff line change
Expand Up @@ -35,21 +35,21 @@ let to_numbered_list = function
| `Two (a, b) ->
[ (0, a); (1, b) ]

let group_sequence : 'a Sequence.t -> 'a t Sequence.t =
fun to_group ->
Sequence.unfold ~init:to_group ~f:(fun acc ->
match Sequence.next acc with
| None ->
None
| Some (a, rest_1) -> (
match Sequence.next rest_1 with
| None ->
Some (`One a, Sequence.empty)
| Some (b, rest_2) ->
Some (`Two (a, b), rest_2) ) )

let group_list : 'a list -> 'a t list =
fun xs -> xs |> Sequence.of_list |> group_sequence |> Sequence.to_list
let f (el, acc) x =
match el with
| `One a ->
(`Two (a, x), acc)
| `Two (a, b) ->
(`One x, `Two (a, b) :: acc)
in
function
| [] ->
[]
| fst_x :: xs ->
let init = (`One fst_x, []) in
let last, res = List.fold ~init ~f xs in
List.rev @@ (last :: res)

let zip : 'a t -> 'b t -> ('a * 'b) t Or_error.t =
fun a b ->
Expand Down
2 changes: 0 additions & 2 deletions src/lib/one_or_two/one_or_two.mli
Original file line number Diff line number Diff line change
Expand Up @@ -24,8 +24,6 @@ val to_list : 'a t -> 'a list

val to_numbered_list : 'a t -> (int * 'a) list

val group_sequence : 'a Sequence.t -> 'a t Sequence.t

val group_list : 'a list -> 'a t list

val zip : 'a t -> 'b t -> ('a * 'b) t Or_error.t
Expand Down
11 changes: 5 additions & 6 deletions src/lib/snark_profiler_lib/snark_profiler_lib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -570,8 +570,7 @@ let profile_user_command (module T : Transaction_snark.S) ~genesis_constants
~f:(fun ((max_span, source_ledger, coinbase_stack_source), proofs)
(target_ledger, applied) ->
let txn =
With_status.data
@@ Mina_ledger.Ledger.transaction_of_applied applied
Mina_transaction_logic.Transaction_applied.transaction applied
in
(* the txn was already valid before apply, we are just recasting it here after application *)
let (`If_this_is_used_it_should_have_a_comment_justifying_it
Expand Down Expand Up @@ -792,8 +791,8 @@ let check_base_snarks ~genesis_constants ~constraint_constants ~logger
|> List.fold ~init:sparse_ledger0
~f:(fun source_ledger (target_ledger, applied_txn) ->
let txn =
With_status.data
@@ Mina_ledger.Ledger.transaction_of_applied applied_txn
Mina_transaction_logic.Transaction_applied.transaction
applied_txn
in
(* the txn was already valid before apply, we are just recasting it here after application *)
let (`If_this_is_used_it_should_have_a_comment_justifying_it
Expand Down Expand Up @@ -857,8 +856,8 @@ let generate_base_snarks_witness ~genesis_constants ~constraint_constants
|> List.fold ~init:sparse_ledger0
~f:(fun source_ledger (target_ledger, applied_txn) ->
let txn =
With_status.data
@@ Mina_ledger.Ledger.transaction_of_applied applied_txn
Mina_transaction_logic.Transaction_applied.transaction
applied_txn
in
(* the txn was already valid before apply, we are just recasting it here after application *)
let (`If_this_is_used_it_should_have_a_comment_justifying_it
Expand Down
17 changes: 1 addition & 16 deletions src/lib/snark_work_lib/metrics.ml
Original file line number Diff line number Diff line change
@@ -1,20 +1,5 @@
open Core_kernel

module Transaction_type = struct
type t = [ `Zkapp_command | `Signed_command | `Coinbase | `Fee_transfer ]
[@@deriving to_yojson]

let of_transaction = function
| Mina_transaction.Transaction.Command
(Mina_base.User_command.Zkapp_command _) ->
`Zkapp_command
| Command (Signed_command _) ->
`Signed_command
| Coinbase _ ->
`Coinbase
| Fee_transfer _ ->
`Fee_transfer
end
module Transaction_type = Mina_transaction.Transaction_type

let emit_single_metrics_impl ~logger
~(single_spec : (Transaction_type.t, _) Single_spec.Poly.t) ~elapsed =
Expand Down
3 changes: 2 additions & 1 deletion src/lib/staged_ledger/pre_diff_info.ml
Original file line number Diff line number Diff line change
Expand Up @@ -403,7 +403,8 @@ let compute_statuses
let split_transaction_statuses txns_with_statuses =
List.partition_map txns_with_statuses ~f:(fun txn_applied ->
let { With_status.data = txn; status } =
Mina_ledger.Ledger.transaction_of_applied txn_applied
Mina_transaction_logic.Transaction_applied.transaction_with_status
txn_applied
in
match txn with
| Transaction.Command cmd ->
Expand Down
Loading