• Home
  • Features
  • Pricing
  • Docs
  • Announcements
  • Sign In

MinaProtocol / mina / 819

19 Nov 2025 08:18PM UTC coverage: 32.092% (-7.2%) from 39.26%
819

Pull #18126

buildkite

dkijania
adjust parameters for release/manager.sh script
Pull Request #18126: [Europe GRC 2/3 ] Remove publish_to_io flag and allow to specify source/target docker repo

23643 of 73672 relevant lines covered (32.09%)

23335.19 hits per line

Source File
Press 'n' to go to next uncovered line, 'b' for previous

0.8
/src/lib/transition_handler/processor.ml
1
(** This module contains the transition processor. The transition processor is
2
 *  the thread in which transitions are attached the to the transition frontier.
3
 *
4
 *  Two types of data are handled by the transition processor: validated external transitions
5
 *  with precomputed state hashes (via the block producer and validator pipes)
6
 *  and breadcrumb rose trees (via the catchup pipe).
7
 *)
8

139✔
9
open Core_kernel
10
open Async_kernel
11
open Pipe_lib.Strict_pipe
12
open Mina_base
13
open Mina_state
14
open Cache_lib
15
open Mina_block
16
open Network_peer
17

18
module type CONTEXT = sig
19
  val logger : Logger.t
20

21
  val precomputed_values : Precomputed_values.t
22

23
  val constraint_constants : Genesis_constants.Constraint_constants.t
24

25
  val consensus_constants : Consensus.Constants.t
26
end
27

28
(* TODO: calculate a sensible value from postake consensus arguments *)
29
let catchup_timeout_duration (precomputed_values : Precomputed_values.t) =
30
  Block_time.Span.of_ms
×
31
    ( (precomputed_values.genesis_constants.protocol.delta + 1)
32
      * precomputed_values.constraint_constants.block_window_duration_ms
33
    |> Int64.of_int )
×
34
  |> Block_time.Span.min (Block_time.Span.of_ms (Int64.of_int 5000))
×
35

36
let cached_transform_deferred_result ~transform_cached ~transform_result cached
37
    =
38
  Cached.transform cached ~f:transform_cached
×
39
  |> Cached.sequence_deferred
×
40
  >>= Fn.compose transform_result Cached.sequence_result
×
41

42
(* add a breadcrumb and perform post processing *)
43
let add_and_finalize ~logger ~frontier ~catchup_scheduler
44
    ~processed_transition_writer ~only_if_present ~time_controller ~source
45
    ~valid_cb cached_breadcrumb ~(precomputed_values : Precomputed_values.t) =
46
  let module Inclusion_time = Mina_metrics.Block_latency.Inclusion_time in
×
47
  let breadcrumb =
48
    if Cached.is_pure cached_breadcrumb then Cached.peek cached_breadcrumb
×
49
    else Cached.invalidate_with_success cached_breadcrumb
×
50
  in
51
  let consensus_constants = precomputed_values.consensus_constants in
52
  let transition =
53
    Transition_frontier.Breadcrumb.validated_transition breadcrumb
54
  in
55
  [%log debug] "add_and_finalize $state_hash %s callback"
×
56
    ~metadata:
57
      [ ( "state_hash"
58
        , Transition_frontier.Breadcrumb.state_hash breadcrumb
×
59
          |> State_hash.to_yojson )
×
60
      ]
61
    (Option.value_map valid_cb ~default:"without" ~f:(const "with")) ;
×
62
  let state_hash = Transition_frontier.Breadcrumb.state_hash breadcrumb in
×
63
  Internal_tracing.with_state_hash state_hash
×
64
  @@ fun () ->
65
  [%log internal] "Add_and_finalize" ;
×
66
  let%map () =
67
    if only_if_present then (
×
68
      let parent_hash = Transition_frontier.Breadcrumb.parent_hash breadcrumb in
69
      match Transition_frontier.find frontier parent_hash with
×
70
      | Some _ ->
×
71
          Transition_frontier.add_breadcrumb_exn frontier breadcrumb
×
72
      | None ->
×
73
          [%log internal] "Parent_breadcrumb_not_found" ;
×
74
          [%log warn]
×
75
            !"When trying to add breadcrumb, its parent had been removed from \
×
76
              transition frontier: %{sexp: State_hash.t}"
77
            parent_hash ;
78
          Deferred.unit )
×
79
    else Transition_frontier.add_breadcrumb_exn frontier breadcrumb
×
80
  in
81
  ( match source with
×
82
  | `Internal ->
×
83
      ()
84
  | _ ->
×
85
      let transition_time =
86
        transition |> Mina_block.Validated.header
×
87
        |> Mina_block.Header.protocol_state |> Protocol_state.consensus_state
×
88
        |> Consensus.Data.Consensus_state.consensus_time
89
      in
90
      let time_elapsed =
×
91
        Block_time.diff
92
          (Block_time.now time_controller)
×
93
          (Consensus.Data.Consensus_time.to_time ~constants:consensus_constants
×
94
             transition_time )
95
      in
96
      Inclusion_time.update (Block_time.Span.to_time_span time_elapsed) ) ;
×
97
  [%log internal] "Add_and_finalize_done" ;
×
98
  if Writer.is_closed processed_transition_writer then
×
99
    Or_error.error_string "processed transitions closed"
×
100
  else (
×
101
    Writer.write processed_transition_writer
102
      (`Transition transition, `Source source, `Valid_cb valid_cb) ;
103
    Catchup_scheduler.notify catchup_scheduler
×
104
      ~hash:(Mina_block.Validated.state_hash transition) )
×
105

106
let process_transition ~context:(module Context : CONTEXT) ~trust_system
107
    ~verifier ~get_completed_work ~frontier ~catchup_scheduler
108
    ~processed_transition_writer ~time_controller ~block_or_header ~valid_cb
109
    ?transaction_pool_proxy =
110
  let is_block_in_frontier =
×
111
    Fn.compose Option.is_some @@ Transition_frontier.find frontier
×
112
  in
113
  let open Context in
×
114
  let header, transition_hash, transition_receipt_time, sender, validation =
115
    match block_or_header with
116
    | `Block cached_env ->
×
117
        let env = Cached.peek cached_env in
118
        let block, v = Envelope.Incoming.data env in
×
119
        ( Mina_block.header @@ With_hash.data block
×
120
        , State_hash.With_state_hashes.state_hash block
×
121
        , Some (Envelope.Incoming.received_at env)
×
122
        , Envelope.Incoming.sender env
×
123
        , v )
124
    | `Header env ->
×
125
        let h, v = Envelope.Incoming.data env in
126
        ( With_hash.data h
×
127
        , State_hash.With_state_hashes.state_hash h
×
128
        , Some (Envelope.Incoming.received_at env)
×
129
        , Envelope.Incoming.sender env
×
130
        , v )
131
  in
132
  let parent_hash =
133
    Protocol_state.previous_state_hash (Header.protocol_state header)
×
134
  in
135
  let root_block =
×
136
    Transition_frontier.(Breadcrumb.block_with_hash @@ root frontier)
×
137
  in
138
  let metadata = [ ("state_hash", State_hash.to_yojson transition_hash) ] in
×
139
  let state_hash = transition_hash in
140
  Internal_tracing.with_state_hash state_hash
141
  @@ fun () ->
142
  [%log internal] "@block_metadata"
×
143
    ~metadata:
144
      [ ( "blockchain_length"
145
        , Mina_numbers.Length.to_yojson (Header.blockchain_length header) )
×
146
      ] ;
147
  [%log internal] "Begin_external_block_processing" ;
×
148
  let handle_not_selected () =
×
149
    [%log internal] "Failure"
×
150
      ~metadata:[ ("reason", `String "Not_selected_over_frontier_root") ] ;
151
    Trust_system.record_envelope_sender trust_system logger sender
×
152
      ( Trust_system.Actions.Gossiped_invalid_transition
153
      , Some
154
          ( "The transition with hash $state_hash was not selected over the \
155
             transition frontier root"
156
          , metadata ) )
157
  in
158
  match block_or_header with
159
  | `Header env -> (
×
160
      let header_with_hash, _ = Envelope.Incoming.data env in
161
      [%log internal] "Validate_frontier_dependencies" ;
×
162
      match
×
163
        Mina_block.Validation.validate_frontier_dependencies
164
          ~context:(module Context)
165
          ~root_block ~is_block_in_frontier ~to_header:ident
166
          (Envelope.Incoming.data env)
×
167
      with
168
      | Ok _ | Error `Parent_missing_from_frontier ->
×
169
          [%log internal] "Schedule_catchup" ;
×
170
          Catchup_scheduler.watch_header catchup_scheduler ~valid_cb
×
171
            ~header_with_hash ;
172
          return ()
×
173
      | Error `Not_selected_over_frontier_root ->
×
174
          handle_not_selected ()
175
      | Error `Already_in_frontier ->
×
176
          [%log internal] "Failure"
×
177
            ~metadata:[ ("reason", `String "Already_in_frontier") ] ;
178
          [%log warn] ~metadata
×
179
            "Refusing to process the transition with hash $state_hash because \
180
             it is already in the transition frontier" ;
181
          return () )
×
182
  | `Block cached_initially_validated_transition ->
×
183
      Deferred.ignore_m
184
      @@
185
      let open Deferred.Result.Let_syntax in
186
      let%bind mostly_validated_transition =
187
        let open Deferred.Let_syntax in
188
        let initially_validated_transition =
189
          Cached.peek cached_initially_validated_transition
×
190
          |> Envelope.Incoming.data
191
        in
192
        [%log internal] "Validate_frontier_dependencies" ;
×
193
        match
×
194
          Mina_block.Validation.validate_frontier_dependencies
195
            ~context:(module Context)
196
            ~root_block ~is_block_in_frontier ~to_header:Mina_block.header
197
            initially_validated_transition
198
        with
199
        | Ok t ->
×
200
            return (Ok t)
×
201
        | Error `Not_selected_over_frontier_root ->
×
202
            let (_ : Mina_block.initial_valid_block Envelope.Incoming.t) =
203
              Cached.invalidate_with_failure
204
                cached_initially_validated_transition
205
            in
206
            let%map () = handle_not_selected () in
×
207
            Error ()
×
208
        | Error `Already_in_frontier ->
×
209
            [%log internal] "Failure"
×
210
              ~metadata:[ ("reason", `String "Already_in_frontier") ] ;
211
            [%log warn] ~metadata
×
212
              "Refusing to process the transition with hash $state_hash \
213
               because is is already in the transition frontier" ;
214
            let (_ : Mina_block.initial_valid_block Envelope.Incoming.t) =
×
215
              Cached.invalidate_with_failure
216
                cached_initially_validated_transition
217
            in
218
            return (Error ())
×
219
        | Error `Parent_missing_from_frontier -> (
×
220
            [%log internal] "Schedule_catchup" ;
×
221
            match validation with
×
222
            | ( _
×
223
              , _
224
              , _
225
              , (`Delta_block_chain, Mina_stdlib.Truth.True delta_state_hashes)
226
              , _
227
              , _
228
              , _ ) ->
229
                let timeout_duration =
230
                  Option.fold
231
                    (Transition_frontier.find frontier
×
232
                       (Mina_stdlib.Nonempty_list.head delta_state_hashes) )
×
233
                    ~init:(Block_time.Span.of_ms 0L)
×
234
                    ~f:(fun _ _ -> catchup_timeout_duration precomputed_values)
×
235
                in
236
                Catchup_scheduler.watch catchup_scheduler ~timeout_duration
×
237
                  ~cached_transition:cached_initially_validated_transition
238
                  ~valid_cb ;
239
                return (Error ()) )
×
240
      in
241
      (* TODO: only access parent in transition frontier once (already done in call to validate dependencies) #2485 *)
242
      [%log internal] "Find_parent_breadcrumb" ;
×
243
      let%bind parent_breadcrumb =
244
        match Transition_frontier.find frontier parent_hash with
245
        | None ->
×
246
            (* Unexpected case: if it happens, there is a bug somewhere. Still,
247
               we should attempt to handle it gracefully. *)
248
            [%log internal] "Failure"
×
249
              ~metadata:[ ("reason", `String "Parent_missing_from_frontier") ] ;
250
            [%log error] ~metadata
×
251
              "Refusing to process the transition with hash $state_hash \
252
               because parent is missing from the transition frontier \
253
               (unexpected case, there is likely a bug somewhere)" ;
254
            let (_ : Mina_block.initial_valid_block Envelope.Incoming.t) =
×
255
              Cached.invalidate_with_failure
256
                cached_initially_validated_transition
257
            in
258
            Deferred.return (Error ())
×
259
        | Some x ->
×
260
            return x
×
261
      in
262
      let%bind breadcrumb =
263
        cached_transform_deferred_result cached_initially_validated_transition
×
264
          ~transform_cached:(fun _ ->
265
            Transition_frontier.Breadcrumb.build ~logger ~precomputed_values
×
266
              ~verifier ~get_completed_work ~trust_system
267
              ~transition_receipt_time ~sender:(Some sender)
268
              ~parent:parent_breadcrumb ~transition:mostly_validated_transition
269
              ?transaction_pool_proxy (* TODO: Can we skip here? *) () )
270
          ~transform_result:(function
271
            | Error (`Invalid_staged_ledger_hash error)
×
272
            | Error (`Invalid_staged_ledger_diff error) ->
×
273
                Internal_tracing.with_state_hash state_hash
274
                @@ fun () ->
275
                [%log internal] "Failure"
×
276
                  ~metadata:[ ("reason", `String (Error.to_string_hum error)) ] ;
×
277
                [%log error]
×
278
                  ~metadata:
279
                    (metadata @ [ ("error", Error_json.error_to_yojson error) ])
×
280
                  "Error while building breadcrumb in the transition handler \
281
                   processor: $error" ;
282
                Deferred.return (Error ())
×
283
            | Error (`Fatal_error exn) ->
×
284
                Internal_tracing.with_state_hash state_hash
285
                @@ fun () ->
286
                [%log internal] "Failure"
×
287
                  ~metadata:[ ("reason", `String "Fatal error") ] ;
288
                raise exn
×
289
            | Ok breadcrumb ->
×
290
                Deferred.return (Ok breadcrumb) )
291
      in
292
      Mina_metrics.(
×
293
        Counter.inc_one
×
294
          Transition_frontier_controller.breadcrumbs_built_by_processor) ;
295
      let%map.Deferred result =
296
        add_and_finalize ~logger ~frontier ~catchup_scheduler
×
297
          ~processed_transition_writer ~only_if_present:false ~time_controller
298
          ~source:`Gossip breadcrumb ~precomputed_values ~valid_cb
299
      in
300
      ( match result with
×
301
      | Ok () ->
×
302
          [%log internal] "Breadcrumb_integrated"
×
303
      | Error err ->
×
304
          [%log internal] "Failure"
×
305
            ~metadata:[ ("reason", `String (Error.to_string_hum err)) ] ) ;
×
306
      Result.return result
307

308
let run ~context:(module Context : CONTEXT) ~verifier ~trust_system
309
    ~time_controller ~frontier ~get_completed_work
310
    ~(primary_transition_reader :
311
       ( [ `Block of
312
           ( Mina_block.initial_valid_block Envelope.Incoming.t
313
           , State_hash.t )
314
           Cached.t
315
         | `Header of Mina_block.initial_valid_header Envelope.Incoming.t ]
316
       * [ `Valid_cb of Mina_net2.Validation_callback.t option ] )
317
       Reader.t )
318
    ~(producer_transition_reader : Transition_frontier.Breadcrumb.t Reader.t)
319
    ~(clean_up_catchup_scheduler : unit Ivar.t) ~catchup_job_writer
320
    ~(catchup_breadcrumbs_reader :
321
       ( ( (Transition_frontier.Breadcrumb.t, State_hash.t) Cached.t
322
         * Mina_net2.Validation_callback.t option )
323
         Mina_stdlib.Rose_tree.t
324
         list
325
       * [ `Ledger_catchup of unit Ivar.t | `Catchup_scheduler ] )
326
       Reader.t )
327
    ~(catchup_breadcrumbs_writer :
328
       ( ( (Transition_frontier.Breadcrumb.t, State_hash.t) Cached.t
329
         * Mina_net2.Validation_callback.t option )
330
         Mina_stdlib.Rose_tree.t
331
         list
332
         * [ `Ledger_catchup of unit Ivar.t | `Catchup_scheduler ]
333
       , crash buffered
334
       , unit )
335
       Writer.t ) ~processed_transition_writer ?transaction_pool_proxy =
336
  let open Context in
×
337
  let catchup_scheduler =
338
    Catchup_scheduler.create ~logger ~precomputed_values ~verifier ~trust_system
339
      ~frontier ~time_controller ~catchup_job_writer ~catchup_breadcrumbs_writer
340
      ~clean_up_signal:clean_up_catchup_scheduler
341
  in
342
  let add_and_finalize =
343
    add_and_finalize ~frontier ~catchup_scheduler ~processed_transition_writer
344
      ~time_controller ~precomputed_values
345
  in
346
  let process_transition =
347
    process_transition
348
      ~context:(module Context)
349
      ~get_completed_work ~trust_system ~verifier ~frontier ~catchup_scheduler
350
      ~processed_transition_writer ~time_controller
351
  in
352
  O1trace.background_thread "process_blocks" (fun () ->
353
      Reader.Merge.iter
×
354
        (* It is fine to skip the cache layer on blocks produced by this node
355
           * because it is extraordinarily unlikely we would write an internal bug
356
           * triggering this case, and the external case (where we received an
357
           * identical external transition from the network) can happen iff there
358
           * is another node with the exact same private key and view of the
359
           * transaction pool. *)
360
        [ Reader.map producer_transition_reader ~f:(fun breadcrumb ->
×
361
              Mina_metrics.(
×
362
                Gauge.inc_one
×
363
                  Transition_frontier_controller.transitions_being_processed) ;
364
              `Local_breadcrumb (Cached.pure breadcrumb) )
×
365
        ; Reader.map catchup_breadcrumbs_reader
×
366
            ~f:(fun (cb, catchup_breadcrumbs_callback) ->
367
              `Catchup_breadcrumbs (cb, catchup_breadcrumbs_callback) )
×
368
        ; Reader.map primary_transition_reader ~f:(fun vt ->
×
369
              `Partially_valid_transition vt )
×
370
        ]
371
        ~f:(fun msg ->
372
          let open Deferred.Let_syntax in
×
373
          O1trace.thread "transition_handler_processor" (fun () ->
374
              match msg with
×
375
              | `Catchup_breadcrumbs
×
376
                  (breadcrumb_subtrees, subsequent_callback_action) -> (
377
                  ( match%map
378
                      Deferred.Or_error.List.iter breadcrumb_subtrees
×
379
                        ~f:(fun subtree ->
380
                          Mina_stdlib.Rose_tree.Deferred.Or_error.iter
×
381
                            subtree
382
                            (* It could be the case that by the time we try and
383
                               * add the breadcrumb, it's no longer relevant when
384
                               * we're catching up *) ~f:(fun (b, valid_cb) ->
385
                              let state_hash =
×
386
                                Frontier_base.Breadcrumb.state_hash
387
                                  (Cached.peek b)
×
388
                              in
389
                              let%map result =
390
                                add_and_finalize ~logger ~only_if_present:true
×
391
                                  ~source:`Catchup ~valid_cb b
392
                              in
393
                              Internal_tracing.with_state_hash state_hash
×
394
                              @@ fun () ->
395
                              ( match result with
×
396
                              | Error err ->
×
397
                                  [%log internal] "Failure"
×
398
                                    ~metadata:
399
                                      [ ( "reason"
400
                                        , `String (Error.to_string_hum err) )
×
401
                                      ]
402
                              | Ok () ->
×
403
                                  [%log internal] "Breadcrumb_integrated" ) ;
×
404
                              result ) )
405
                    with
406
                  | Ok () ->
×
407
                      ()
408
                  | Error err ->
×
409
                      List.iter breadcrumb_subtrees ~f:(fun tree ->
410
                          Mina_stdlib.Rose_tree.iter tree
×
411
                            ~f:(fun (cached_breadcrumb, _vc) ->
412
                              let (_ : Transition_frontier.Breadcrumb.t) =
×
413
                                Cached.invalidate_with_failure cached_breadcrumb
414
                              in
415
                              () ) ) ;
×
416
                      [%log error]
×
417
                        "Error, failed to attach all catchup breadcrumbs to \
418
                         transition frontier: $error"
419
                        ~metadata:[ ("error", Error_json.error_to_yojson err) ]
×
420
                  )
421
                  >>| fun () ->
422
                  match subsequent_callback_action with
×
423
                  | `Ledger_catchup decrement_signal ->
×
424
                      if Ivar.is_full decrement_signal then
425
                        [%log error] "Ivar.fill bug is here!" ;
×
426
                      Ivar.fill decrement_signal ()
×
427
                  | `Catchup_scheduler ->
×
428
                      () )
429
              | `Local_breadcrumb breadcrumb ->
×
430
                  let state_hash =
431
                    Transition_frontier.Breadcrumb.validated_transition
×
432
                      (Cached.peek breadcrumb)
×
433
                    |> Mina_block.Validated.state_hash
434
                  in
435
                  Internal_tracing.with_state_hash state_hash
×
436
                  @@ fun () ->
437
                  [%log internal] "Begin_local_block_processing" ;
×
438
                  let transition_time =
×
439
                    Transition_frontier.Breadcrumb.validated_transition
×
440
                      (Cached.peek breadcrumb)
×
441
                    |> Mina_block.Validated.header
×
442
                    |> Mina_block.Header.protocol_state
×
443
                    |> Protocol_state.blockchain_state
×
444
                    |> Blockchain_state.timestamp |> Block_time.to_time_exn
×
445
                  in
446
                  Perf_histograms.add_span
×
447
                    ~name:"accepted_transition_local_latency"
448
                    (Core_kernel.Time.diff
×
449
                       Block_time.(now time_controller |> to_time_exn)
×
450
                       transition_time ) ;
451
                  let%map () =
452
                    match%map
453
                      add_and_finalize ~logger ~only_if_present:false
×
454
                        ~source:`Internal breadcrumb ~valid_cb:None
455
                    with
456
                    | Ok () ->
×
457
                        [%log internal] "Breadcrumb_integrated" ;
×
458
                        ()
×
459
                    | Error err ->
×
460
                        [%log internal] "Failure"
×
461
                          ~metadata:
462
                            [ ("reason", `String (Error.to_string_hum err)) ] ;
×
463
                        [%log error]
×
464
                          ~metadata:
465
                            [ ("error", Error_json.error_to_yojson err) ]
×
466
                          "Error, failed to attach produced breadcrumb to \
467
                           transition frontier: $error" ;
468
                        let (_ : Transition_frontier.Breadcrumb.t) =
×
469
                          Cached.invalidate_with_failure breadcrumb
470
                        in
471
                        ()
×
472
                  in
473
                  Mina_metrics.(
×
474
                    Gauge.dec_one
475
                      Transition_frontier_controller.transitions_being_processed)
476
              | `Partially_valid_transition (block_or_header, `Valid_cb valid_cb)
×
477
                ->
478
                  process_transition ~block_or_header ~valid_cb
479
                    ?transaction_pool_proxy ) ) )
480

481
let%test_module "Transition_handler.Processor tests" =
482
  ( module struct
483
    open Async
484
    open Pipe_lib
485

486
    let () =
487
      Backtrace.elide := false ;
488
      Printexc.record_backtrace true ;
489
      Async.Scheduler.set_record_backtraces true
×
490

491
    let logger = Logger.null ()
×
492

493
    let () =
494
      (* Disable log messages from best_tip_diff logger. *)
495
      Logger.Consumer_registry.register ~commit_id:""
×
496
        ~id:Logger.Logger_id.best_tip_diff ~processor:(Logger.Processor.raw ())
×
497
        ~transport:
498
          (Logger.Transport.create
×
499
             ( module struct
500
               type t = unit
501

502
               let transport () _ = ()
×
503
             end )
504
             () )
505
        ()
506

507
    let precomputed_values = Lazy.force Precomputed_values.for_unit_tests
×
508

509
    let proof_level = precomputed_values.proof_level
510

511
    let constraint_constants = precomputed_values.constraint_constants
512

513
    let time_controller = Block_time.Controller.basic ~logger
514

515
    let trust_system = Trust_system.null ()
×
516

517
    let verifier =
518
      Async.Thread_safe.block_on_async_exn (fun () ->
×
519
          Verifier.For_tests.default ~constraint_constants ~logger ~proof_level
×
520
            () )
521

522
    module Context = struct
523
      let logger = logger
524

525
      let precomputed_values = precomputed_values
526

527
      let constraint_constants = constraint_constants
528

529
      let consensus_constants = precomputed_values.consensus_constants
530
    end
531

532
    let downcast_breadcrumb breadcrumb =
533
      let transition =
×
534
        Transition_frontier.Breadcrumb.validated_transition breadcrumb
×
535
        |> Mina_block.Validated.remember
×
536
        |> Mina_block.Validation.reset_frontier_dependencies_validation
×
537
        |> Mina_block.Validation.reset_staged_ledger_diff_validation
538
      in
539
      Envelope.Incoming.wrap ~data:transition ~sender:Envelope.Sender.Local
×
540

541
    let%test_unit "adding transitions whose parents are in the frontier" =
542
      let frontier_size = 1 in
×
543
      let branch_size = 10 in
544
      let max_length = frontier_size + branch_size in
545
      Quickcheck.test ~trials:4
546
        (Transition_frontier.For_tests.gen_with_branch ~precomputed_values
×
547
           ~verifier ~max_length ~frontier_size ~branch_size () )
548
        ~f:(fun (frontier, branch) ->
549
          assert (
×
550
            Thread_safe.block_on_async_exn (fun () ->
×
551
                let valid_transition_reader, valid_transition_writer =
×
552
                  Strict_pipe.create
553
                    (Buffered
554
                       (`Capacity branch_size, `Overflow (Drop_head ignore)) )
555
                in
556
                let producer_transition_reader, _ =
×
557
                  Strict_pipe.create
558
                    (Buffered
559
                       (`Capacity branch_size, `Overflow (Drop_head ignore)) )
560
                in
561
                let _, catchup_job_writer =
×
562
                  Strict_pipe.create (Buffered (`Capacity 1, `Overflow Crash))
563
                in
564
                let catchup_breadcrumbs_reader, catchup_breadcrumbs_writer =
×
565
                  Strict_pipe.create (Buffered (`Capacity 1, `Overflow Crash))
566
                in
567
                let processed_transition_reader, processed_transition_writer =
×
568
                  Strict_pipe.create
569
                    (Buffered
570
                       (`Capacity branch_size, `Overflow (Drop_head ignore)) )
571
                in
572
                let clean_up_catchup_scheduler = Ivar.create () in
×
573
                let cache =
×
574
                  Unprocessed_transition_cache.create ~logger
575
                    ~cache_exceptions:true
576
                in
577
                run
578
                  ~context:(module Context)
579
                  ~time_controller ~verifier ~get_completed_work:(Fn.const None)
×
580
                  ~trust_system ~clean_up_catchup_scheduler ~frontier
581
                  ~primary_transition_reader:valid_transition_reader
582
                  ~producer_transition_reader ~catchup_job_writer
583
                  ~catchup_breadcrumbs_reader ~catchup_breadcrumbs_writer
584
                  ~processed_transition_writer ?transaction_pool_proxy:None ;
585
                List.iter branch ~f:(fun breadcrumb ->
586
                    let b =
×
587
                      downcast_breadcrumb breadcrumb
×
588
                      |> Unprocessed_transition_cache.register_exn cache
589
                    in
590
                    Strict_pipe.Writer.write valid_transition_writer
×
591
                      (`Block b, `Valid_cb None) ) ;
592
                match%map
593
                  Block_time.Timeout.await
×
594
                    ~timeout_duration:(Block_time.Span.of_ms 30000L)
×
595
                    time_controller
596
                    (Strict_pipe.Reader.fold_until processed_transition_reader
×
597
                       ~init:branch
598
                       ~f:(fun
599
                            remaining_breadcrumbs
600
                            (`Transition newly_added_transition, _, _)
601
                          ->
602
                         Deferred.return
×
603
                           ( match remaining_breadcrumbs with
604
                           | next_expected_breadcrumb :: tail ->
×
605
                               [%test_eq: State_hash.t]
×
606
                                 (Transition_frontier.Breadcrumb.state_hash
×
607
                                    next_expected_breadcrumb )
608
                                 (Mina_block.Validated.state_hash
×
609
                                    newly_added_transition ) ;
610
                               [%log info]
×
611
                                 ~metadata:
612
                                   [ ( "height"
613
                                     , `Int
614
                                         ( newly_added_transition
615
                                         |> Mina_block.Validated.forget
×
616
                                         |> With_hash.data |> Mina_block.header
×
617
                                         |> Mina_block.Header.protocol_state
×
618
                                         |> Protocol_state.consensus_state
×
619
                                         |> Consensus.Data.Consensus_state
620
                                            .blockchain_length
×
621
                                         |> Mina_numbers.Length.to_uint32
×
622
                                         |> Unsigned.UInt32.to_int ) )
×
623
                                   ]
624
                                 "transition of $height passed processor" ;
625
                               if List.is_empty tail then `Stop true
×
626
                               else `Continue tail
×
627
                           | [] ->
×
628
                               `Stop false ) ) )
629
                with
630
                | `Timeout ->
×
631
                    failwith "test timed out"
632
                | `Ok (`Eof _) ->
×
633
                    failwith "pipe closed unexpectedly"
634
                | `Ok (`Terminated x) ->
×
635
                    x ) ) )
636
  end )
278✔
STATUS · Troubleshooting · Open an Issue · Sales · Support · CAREERS · ENTERPRISE · START FREE · SCHEDULE DEMO
ANNOUNCEMENTS · TWITTER · TOS & SLA · Supported CI Services · What's a CI service? · Automated Testing

© 2026 Coveralls, Inc