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

MinaProtocol / mina / 2863

05 Nov 2024 06:20PM UTC coverage: 30.754% (-16.6%) from 47.311%
2863

push

buildkite

web-flow
Merge pull request #16296 from MinaProtocol/dkijania/more_multi_jobs

more multi jobs in CI

20276 of 65930 relevant lines covered (30.75%)

8631.7 hits per line

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

8.47
/src/lib/rosetta_lib/user_command_info.ml
1
open Core_kernel
2✔
2
module Fee_currency = Currency.Fee
3
module Amount_currency = Currency.Amount
4
open Rosetta_models
5
module Signed_command = Mina_base.Signed_command
6
module Token_id = Mina_base.Token_id
7
module Public_key = Signature_lib.Public_key
8
module Signed_command_memo = Mina_base.Signed_command_memo
9
module Payment_payload = Mina_base.Payment_payload
10
module Stake_delegation = Mina_base.Stake_delegation
11

12
let pk_to_public_key ~context (`Pk pk) =
13
  Public_key.Compressed.of_base58_check pk
×
14
  |> Result.map_error ~f:(fun _ ->
×
15
         Errors.create ~context `Public_key_format_not_valid )
×
16

17
let account_id (`Pk pk) (`Token_id token_id) =
18
  { Account_identifier.address = pk
×
19
  ; sub_account = None
20
  ; metadata = Some (Amount_of.Token_id.encode token_id)
×
21
  }
22

23
let token_id_of_account (account : Account_identifier.t) =
24
  let module Decoder = Amount_of.Token_id.T (Result) in
×
25
  Decoder.decode account.metadata
26
  |> Result.map ~f:(Option.value ~default:Amount_of.Token_id.default)
×
27
  |> Result.ok
×
28

29
module Op = struct
30
  type 'a t = { label : 'a; related_to : 'a option } [@@deriving equal]
×
31

32
  module T (M : Monad.S2) = struct
33
    let build ~a_eq ~plan ~f =
34
      let open M.Let_syntax in
×
35
      let%map _, rev_data =
36
        List.fold plan
×
37
          ~init:(M.return (0, []))
×
38
          ~f:(fun macc op ->
39
            let open M.Let_syntax in
×
40
            let%bind i, acc = macc in
41
            let operation_identifier i =
×
42
              { Operation_identifier.index = Int64.of_int_exn i
×
43
              ; network_index = None
44
              }
45
            in
46
            let related_operations =
47
              op.related_to
48
              |> Option.bind ~f:(fun relate ->
49
                     List.findi plan ~f:(fun _ a -> a_eq relate a.label) )
×
50
              |> Option.map ~f:(fun (i, _) -> [ operation_identifier i ])
×
51
              |> Option.value ~default:[]
×
52
            in
53
            let%map a =
54
              f ~related_operations
×
55
                ~operation_identifier:(operation_identifier i) op
×
56
            in
57
            (i + 1, a :: acc) )
×
58
      in
59
      List.rev rev_data
×
60
  end
61

62
  module Ident2 = struct
63
    type ('a, 'e) t = 'a
64

65
    module T = struct
66
      type ('a, 'e) t = 'a
67

68
      let map = `Define_using_bind
69

70
      let return a = a
×
71

72
      let bind a ~f = f a
×
73
    end
74

75
    include Monad.Make2 (T)
76
  end
77

78
  include T (Ident2)
79
end
80

81
module Kind = struct
82
  type t = [ `Payment | `Delegation ] [@@deriving yojson, equal, sexp, compare]
×
83
end
84

85
module Account_creation_fees_paid = struct
86
  type t = By_no_one | By_receiver of Unsigned_extended.UInt64.t
×
87
  [@@deriving equal, to_yojson, sexp, compare]
88
end
89

90
module Failure_status = struct
91
  type t = [ `Applied of Account_creation_fees_paid.t | `Failed of string ]
×
92
  [@@deriving equal, to_yojson, sexp, compare]
×
93
end
94

95
type t =
×
96
  { kind : Kind.t
×
97
  ; fee_payer : [ `Pk of string ]
×
98
  ; source : [ `Pk of string ]
×
99
  ; receiver : [ `Pk of string ]
×
100
  ; fee_token : [ `Token_id of string ]
×
101
  ; token : [ `Token_id of string ]
×
102
  ; fee : Unsigned_extended.UInt64.t
×
103
  ; nonce : Unsigned_extended.UInt32.t
×
104
  ; amount : Unsigned_extended.UInt64.t option
×
105
  ; valid_until : Unsigned_extended.UInt32.t option
×
106
  ; memo : string option
×
107
  ; hash : string
×
108
  ; failure_status : Failure_status.t option
×
109
  }
110
[@@deriving to_yojson, equal, sexp, compare]
×
111

112
module Partial = struct
113
  type t =
×
114
    { kind : Kind.t
×
115
    ; fee_payer : [ `Pk of string ]
×
116
    ; source : [ `Pk of string ]
×
117
    ; receiver : [ `Pk of string ]
×
118
    ; fee_token : [ `Token_id of string ]
×
119
    ; token : [ `Token_id of string ]
×
120
    ; fee : Unsigned_extended.UInt64.t
×
121
    ; amount : Unsigned_extended.UInt64.t option
×
122
    ; valid_until : Unsigned_extended.UInt32.t option
×
123
    ; memo : string option
×
124
    }
125
  [@@deriving to_yojson, sexp, compare, equal]
×
126

127
  module Reason = Errors.Partial_reason
128

129
  let to_user_command_payload :
130
         t
131
      -> nonce:Unsigned_extended.UInt32.t
132
      -> (Signed_command.Payload.t, Errors.t) Result.t =
133
   fun t ~nonce ->
134
    let open Result.Let_syntax in
×
135
    let%bind fee_payer_pk = pk_to_public_key ~context:"Fee payer" t.fee_payer in
×
136
    let%bind source_pk = pk_to_public_key ~context:"Source" t.source in
×
137
    let%bind receiver_pk = pk_to_public_key ~context:"Receiver" t.receiver in
×
138
    let%bind () =
139
      Result.ok_if_true
×
140
        (Public_key.Compressed.equal fee_payer_pk source_pk)
×
141
        ~error:
142
          (Errors.create
×
143
             (`Operations_not_valid
144
               [ Errors.Partial_reason.Fee_payer_and_source_mismatch ] ) )
145
    in
146
    let%bind memo =
147
      match t.memo with
148
      | Some memo -> (
×
149
          try Ok (Signed_command_memo.create_from_string_exn memo)
×
150
          with _ -> Error (Errors.create `Memo_invalid) )
×
151
      | None ->
×
152
          Ok Signed_command_memo.empty
153
    in
154
    let%map body =
155
      match t.kind with
156
      | `Payment ->
×
157
          let%map amount =
158
            Result.of_option t.amount
×
159
              ~error:
160
                (Errors.create
×
161
                   (`Operations_not_valid
162
                     [ Errors.Partial_reason.Amount_not_some ] ) )
163
          in
164
          let payload =
×
165
            { Payment_payload.Poly.receiver_pk
166
            ; amount = Amount_currency.of_uint64 amount
×
167
            }
168
          in
169
          Signed_command.Payload.Body.Payment payload
170
      | `Delegation ->
×
171
          let payload =
172
            Stake_delegation.Set_delegate { new_delegate = receiver_pk }
173
          in
174
          Result.return @@ Signed_command.Payload.Body.Stake_delegation payload
×
175
    in
176
    Signed_command.Payload.create
×
177
      ~fee:(Fee_currency.of_uint64 t.fee)
×
178
      ~fee_payer_pk ~nonce ~body ~memo
179
      ~valid_until:
180
        (Option.map ~f:Mina_numbers.Global_slot_since_genesis.of_uint32
×
181
           t.valid_until )
182
end
183

184
let forget (t : t) : Partial.t =
185
  { kind = t.kind
×
186
  ; fee_payer = t.fee_payer
187
  ; source = t.source
188
  ; receiver = t.receiver
189
  ; fee_token = t.fee_token
190
  ; token = t.token
191
  ; fee = t.fee
192
  ; amount = t.amount
193
  ; valid_until = t.valid_until
194
  ; memo = t.memo
195
  }
196

197
let remember ~nonce ~hash t =
198
  { kind = t.kind
×
199
  ; fee_payer = t.fee_payer
200
  ; source = t.source
201
  ; receiver = t.receiver
202
  ; fee_token = t.fee_token
203
  ; token = t.token
204
  ; fee = t.fee
205
  ; amount = t.amount
206
  ; valid_until = t.valid_until
207
  ; memo = t.memo
208
  ; hash
209
  ; nonce
210
  ; failure_status = None
211
  }
212

213
let of_operations ?memo ?valid_until (ops : Operation.t list) :
214
    (Partial.t, Partial.Reason.t) Validation.t =
215
  (* TODO: If we care about DoS attacks, break early if length too large *)
216
  (* Note: It's better to have nice errors with the validation than micro-optimize searching through a small list a minimal number of times. *)
217
  let find_kind k (ops : Operation.t list) =
×
218
    let name = Operation_types.name k in
×
219
    List.find ops ~f:(fun op -> String.equal op.Operation._type name)
×
220
    |> Result.of_option ~error:[ Partial.Reason.Can't_find_kind name ]
×
221
  in
222
  let module V = Validation in
223
  let open V.Let_syntax in
224
  let open Partial.Reason in
225
  (* For a payment we demand:
226
     *
227
     * ops = length exactly 3
228
     *
229
     * payment_source_dec with account 'a, some amount 'x, status=None
230
     * fee_payment with account 'a, some amount 'y, status=None
231
     * payment_receiver_inc with account 'b, some amount 'x, status=None
232
  *)
233
  let payment =
234
    let%map () =
235
      if Mina_stdlib.List.Length.Compare.(ops = 3) then V.return ()
×
236
      else V.fail Length_mismatch
×
237
    and account_a =
238
      let open Result.Let_syntax in
239
      let%bind { account; _ } = find_kind `Payment_source_dec ops
×
240
      and { account = account'; _ } = find_kind `Fee_payment ops in
×
241
      match (account, account') with
×
242
      | Some x, Some y when Account_identifier.equal x y ->
×
243
          V.return x
×
244
      | Some _, Some _ ->
×
245
          V.fail Fee_payer_and_source_mismatch
246
      | None, _ | _, None ->
×
247
          V.fail Account_not_some
248
    and token =
249
      let open Result.Let_syntax in
250
      let%bind { account; _ } = find_kind `Payment_source_dec ops in
×
251
      match account with
×
252
      | Some account -> (
×
253
          match token_id_of_account account with
254
          | None ->
×
255
              V.fail Incorrect_token_id
256
          | Some token ->
×
257
              V.return (`Token_id token) )
258
      | None ->
×
259
          V.fail Account_not_some
260
    and fee_token =
261
      let open Result.Let_syntax in
262
      let%bind { account; _ } = find_kind `Fee_payment ops in
×
263
      match account with
×
264
      | Some account -> (
×
265
          match token_id_of_account account with
266
          | Some token_id ->
×
267
              V.return (`Token_id token_id)
268
          | None ->
×
269
              V.fail Incorrect_token_id )
270
      | None ->
×
271
          V.fail Account_not_some
272
    and account_b =
273
      let open Result.Let_syntax in
274
      let%bind { account; _ } = find_kind `Payment_receiver_inc ops in
×
275
      Result.of_option account ~error:[ Account_not_some ]
×
276
    and () =
277
      if
278
        List.for_all ops ~f:(fun op ->
279
            let p = Option.equal String.equal op.status in
×
280
            p None || p (Some "") )
×
281
      then V.return ()
×
282
      else V.fail Status_not_pending
×
283
    and payment_amount_x =
284
      let open Result.Let_syntax in
285
      let%bind { amount; _ } = find_kind `Payment_source_dec ops
×
286
      and { amount = amount'; _ } = find_kind `Payment_receiver_inc ops in
×
287
      match (amount, amount') with
×
288
      | Some x, Some y when Amount.equal (Amount_of.negated x) y ->
×
289
          V.return y
×
290
      | Some _, Some _ ->
×
291
          V.fail Amount_inc_dec_mismatch
292
      | None, _ | _, None ->
×
293
          V.fail Amount_not_some
294
    and payment_amount_y =
295
      let open Result.Let_syntax in
296
      let%bind { amount; _ } = find_kind `Fee_payment ops in
×
297
      match amount with
×
298
      | Some x when Amount_of.compare_to_int64 x 0L < 1 ->
×
299
          V.return (Amount_of.negated x)
×
300
      | Some _ ->
×
301
          V.fail Fee_not_negative
302
      | None ->
×
303
          V.fail Amount_not_some
304
    in
305
    { Partial.kind = `Payment
×
306
    ; fee_payer = `Pk account_a.address
307
    ; source = `Pk account_a.address
308
    ; receiver = `Pk account_b.address
309
    ; fee_token
310
    ; token (* TODO: Catch exception properly on these uint64 decodes *)
311
    ; fee = Unsigned.UInt64.of_string payment_amount_y.Amount.value
×
312
    ; amount = Some (Unsigned.UInt64.of_string payment_amount_x.Amount.value)
×
313
    ; valid_until
314
    ; memo
315
    }
316
  in
317
  (* For a delegation we demand:
318
     *
319
     * ops = length exactly 2
320
     *
321
     * fee_payment with account 'a, some amount 'y, status=None
322
     * delegate_change with account 'a, metadata:{delegate_change_target:'b}, status="Pending"
323
  *)
324
  let delegation =
325
    let%map () =
326
      if Mina_stdlib.List.Length.Compare.(ops = 2) then V.return ()
×
327
      else V.fail Length_mismatch
×
328
    and account_a =
329
      let open Result.Let_syntax in
330
      let%bind { account; _ } = find_kind `Fee_payment ops in
×
331
      Option.value_map account ~default:(V.fail Account_not_some) ~f:V.return
×
332
    and fee_token =
333
      let open Result.Let_syntax in
334
      let%bind { account; _ } = find_kind `Fee_payment ops in
×
335
      match account with
×
336
      | Some account -> (
×
337
          match token_id_of_account account with
338
          | Some token_id ->
×
339
              V.return (`Token_id token_id)
340
          | None ->
×
341
              V.fail Incorrect_token_id )
342
      | None ->
×
343
          V.fail Account_not_some
344
    and account_b =
345
      let open Result.Let_syntax in
346
      let%bind { metadata; _ } = find_kind `Delegate_change ops in
×
347
      match metadata with
×
348
      | Some metadata -> (
×
349
          match metadata with
350
          | `Assoc [ ("delegate_change_target", `String s) ] ->
×
351
              return s
352
          | _ ->
×
353
              V.fail Invalid_metadata )
354
      | None ->
×
355
          V.fail Account_not_some
356
    and () =
357
      if
358
        List.for_all ops ~f:(fun op ->
359
            let p = Option.equal String.equal op.status in
×
360
            p None || p (Some "") )
×
361
      then V.return ()
×
362
      else V.fail Status_not_pending
×
363
    and payment_amount_y =
364
      let open Result.Let_syntax in
365
      let%bind { amount; _ } = find_kind `Fee_payment ops in
×
366
      match amount with
×
367
      | Some x ->
×
368
          V.return (Amount_of.negated x)
×
369
      | None ->
×
370
          V.fail Amount_not_some
371
    in
372
    { Partial.kind = `Delegation
×
373
    ; fee_payer = `Pk account_a.address
374
    ; source = `Pk account_a.address
375
    ; receiver = `Pk account_b
376
    ; fee_token
377
    ; token =
378
        `Token_id Token_id.(default |> to_string)
×
379
        (* only default token can be delegated *)
380
    ; fee = Unsigned.UInt64.of_string payment_amount_y.Amount.value
×
381
    ; amount = None
382
    ; valid_until
383
    ; memo
384
    }
385
  in
386
  let partials = [ payment; delegation ] in
387
  let oks, errs = List.partition_map partials ~f:Result.to_either in
388
  match (oks, errs) with
×
389
  | [], errs ->
×
390
      (* no Oks *)
391
      Error (List.concat errs)
×
392
  | [ partial ], _ ->
×
393
      (* exactly one Ok *)
394
      Ok partial
395
  | _, _ ->
×
396
      (* more than one Ok, a bug in our implementation *)
397
      failwith
398
        "A sequence of operations must represent exactly one user command"
399

400
let to_operations ~failure_status (t : Partial.t) : Operation.t list =
401
  (* First build a plan. The plan specifies all operations ahead of time so
402
     * we can later compute indices and relations when we're building the full
403
     * models.
404
     *
405
     * For now, relations will be defined only on the two sides of a given
406
     * transfer. ie. Source decreases, and receiver increases.
407
  *)
408
  let plan : 'a Op.t list =
×
409
    ( if not Unsigned.UInt64.(equal t.fee zero) then
×
410
      [ { Op.label = `Fee_payment; related_to = None } ]
×
411
    else [] )
×
412
    @ ( match failure_status with
413
      | Some (`Applied (Account_creation_fees_paid.By_receiver amount)) ->
×
414
          [ { Op.label = `Account_creation_fee_via_payment amount
415
            ; related_to = None
416
            }
417
          ]
418
      | _ ->
×
419
          [] )
420
    @
421
    match t.kind with
422
    | `Payment -> (
×
423
        (* When amount is not none, we move the amount from source to receiver -- unless it's a failure, we will capture that below *)
424
        match t.amount with
425
        | Some amount ->
×
426
            [ { Op.label = `Payment_source_dec amount; related_to = None }
427
            ; { Op.label = `Payment_receiver_inc amount
428
              ; related_to = Some (`Payment_source_dec amount)
429
              }
430
            ]
431
        | None ->
×
432
            [] )
433
    | `Delegation ->
×
434
        [ { Op.label = `Delegate_change; related_to = None } ]
435
  in
436
  Op.build
437
    ~a_eq:
438
      [%eq:
439
        [ `Fee_payment
×
440
        | `Payment_source_dec of Unsigned.UInt64.t
441
        | `Payment_receiver_inc of Unsigned.UInt64.t ]] ~plan
×
442
    ~f:(fun ~related_operations ~operation_identifier op ->
443
      let status, metadata, did_fail =
×
444
        match (op.label, failure_status) with
445
        (* If we're looking at mempool transactions, it's always pending *)
446
        | _, None ->
×
447
            (None, None, false)
448
        | _, Some (`Applied _) ->
×
449
            (Some `Success, None, false)
450
        | _, Some (`Failed reason) ->
×
451
            (Some `Failed, Some (`Assoc [ ("reason", `String reason) ]), true)
452
      in
453
      let pending_or_success_only = function
454
        | None ->
×
455
            None
456
        | Some (`Success | `Failed) ->
×
457
            Some `Success
458
      in
459
      let merge_metadata m1 m2 =
460
        match (m1, m2) with
×
461
        | None, None ->
×
462
            None
463
        | Some x, None | None, Some x ->
×
464
            Some x
465
        | Some (`Assoc xs), Some (`Assoc ys) ->
×
466
            Some (`Assoc (xs @ ys))
467
        | _ ->
×
468
            failwith "Unexpected pattern"
469
      in
470
      match op.label with
471
      | `Fee_payment ->
×
472
          { Operation.operation_identifier
473
          ; related_operations
474
          ; status =
475
              status |> pending_or_success_only
476
              |> Option.map ~f:Operation_statuses.name
×
477
          ; account = Some (account_id t.fee_payer t.fee_token)
×
478
          ; _type = Operation_types.name `Fee_payment
×
479
          ; amount = Some Amount_of.(negated @@ token t.fee_token t.fee)
×
480
          ; coin_change = None
481
          ; metadata
482
          }
483
      | `Payment_source_dec amount ->
×
484
          { Operation.operation_identifier
485
          ; related_operations
486
          ; status = Option.map ~f:Operation_statuses.name status
×
487
          ; account = Some (account_id t.source t.token)
×
488
          ; _type = Operation_types.name `Payment_source_dec
×
489
          ; amount =
490
              ( if did_fail then None
×
491
              else Some Amount_of.(negated @@ token t.token amount) )
×
492
          ; coin_change = None
493
          ; metadata
494
          }
495
      | `Payment_receiver_inc amount ->
×
496
          { Operation.operation_identifier
497
          ; related_operations
498
          ; status = Option.map ~f:Operation_statuses.name status
×
499
          ; account = Some (account_id t.receiver t.token)
×
500
          ; _type = Operation_types.name `Payment_receiver_inc
×
501
          ; amount =
502
              (if did_fail then None else Some (Amount_of.token t.token amount))
×
503
          ; coin_change = None
504
          ; metadata
505
          }
506
      | `Account_creation_fee_via_payment account_creation_fee ->
×
507
          { Operation.operation_identifier
508
          ; related_operations
509
          ; status = Option.map ~f:Operation_statuses.name status
×
510
          ; account = Some (account_id t.receiver t.token)
×
511
          ; _type = Operation_types.name `Account_creation_fee_via_payment
×
512
          ; amount = Some Amount_of.(negated @@ mina account_creation_fee)
×
513
          ; coin_change = None
514
          ; metadata
515
          }
516
      | `Delegate_change ->
×
517
          { Operation.operation_identifier
518
          ; related_operations
519
          ; status = Option.map ~f:Operation_statuses.name status
×
520
          ; account =
521
              Some (account_id t.source (`Token_id Amount_of.Token_id.default))
×
522
          ; _type = Operation_types.name `Delegate_change
×
523
          ; amount = None
524
          ; coin_change = None
525
          ; metadata =
526
              merge_metadata metadata
×
527
                (Some
528
                   (`Assoc
529
                     [ ( "delegate_change_target"
530
                       , `String
531
                           (let (`Pk r) = t.receiver in
532
                            r ) )
533
                     ] ) )
534
          } )
535

536
let to_operations' (t : t) : Operation.t list =
537
  to_operations ~failure_status:t.failure_status (forget t)
×
538

539
let%test_unit "payment_round_trip" =
540
  let start =
×
541
    { kind = `Payment (* default token *)
542
    ; fee_payer = `Pk "Alice"
543
    ; source = `Pk "Alice"
544
    ; token = `Token_id Amount_of.Token_id.default
545
    ; fee = Unsigned.UInt64.of_int 2_000_000_000
×
546
    ; receiver = `Pk "Bob"
547
    ; fee_token = `Token_id Amount_of.Token_id.default
548
    ; nonce = Unsigned.UInt32.of_int 3
×
549
    ; amount = Some (Unsigned.UInt64.of_int 2_000_000_000)
×
550
    ; failure_status = None
551
    ; hash = "TXN_1_HASH"
552
    ; valid_until = Some (Unsigned.UInt32.of_int 10_000)
×
553
    ; memo = Some "hello"
554
    }
555
  in
556
  let ops = to_operations' start in
557
  match of_operations ?valid_until:start.valid_until ?memo:start.memo ops with
×
558
  | Ok partial ->
×
559
      [%test_eq: Partial.t] partial (forget start)
×
560
  | Error e ->
×
561
      failwithf !"Mismatch because %{sexp: Partial.Reason.t list}" e ()
×
562

563
let%test_unit "delegation_round_trip" =
564
  let start =
×
565
    { kind = `Delegation
566
    ; fee_payer = `Pk "Alice"
567
    ; source = `Pk "Alice"
568
    ; token = `Token_id Amount_of.Token_id.default
569
    ; fee = Unsigned.UInt64.of_int 1_000_000_000
×
570
    ; receiver = `Pk "Bob"
571
    ; fee_token = `Token_id Amount_of.Token_id.default
572
    ; nonce = Unsigned.UInt32.of_int 42
×
573
    ; amount = None
574
    ; failure_status = None
575
    ; hash = "TXN_2_HASH"
576
    ; valid_until = Some (Unsigned.UInt32.of_int 867888)
×
577
    ; memo = Some "hello"
578
    }
579
  in
580
  let ops = to_operations' start in
581
  match of_operations ops ?valid_until:start.valid_until ?memo:start.memo with
×
582
  | Ok partial ->
×
583
      [%test_eq: Partial.t] partial (forget start)
×
584
  | Error e ->
×
585
      failwithf !"Mismatch because %{sexp: Partial.Reason.t list}" e ()
×
586

587
let non_default_token =
588
  `Token_id
589
    (Token_id.to_string (Quickcheck.random_value Token_id.gen_non_default))
2✔
590

591
let dummies =
592
  [ { kind = `Payment (* default token *)
593
    ; fee_payer = `Pk "Alice"
594
    ; source = `Pk "Alice"
595
    ; token = `Token_id Amount_of.Token_id.default
596
    ; fee_token = `Token_id Amount_of.Token_id.default
597
    ; fee = Unsigned.UInt64.of_int 2_000_000_000
2✔
598
    ; receiver = `Pk "Bob"
599
    ; nonce = Unsigned.UInt32.of_int 3
2✔
600
    ; amount = Some (Unsigned.UInt64.of_int 2_000_000_000)
2✔
601
    ; failure_status = Some (`Applied Account_creation_fees_paid.By_no_one)
602
    ; hash = "TXN_1_HASH"
603
    ; valid_until = None
604
    ; memo = Some "hello"
605
    }
606
  ; { kind = `Payment (* new account created *)
607
    ; fee_payer = `Pk "Alice"
608
    ; source = `Pk "Alice"
609
    ; token = `Token_id Amount_of.Token_id.default
610
    ; fee_token = `Token_id Amount_of.Token_id.default
611
    ; fee = Unsigned.UInt64.of_int 2_000_000_000
2✔
612
    ; receiver = `Pk "Bob"
613
    ; nonce = Unsigned.UInt32.of_int 3
2✔
614
    ; amount = Some (Unsigned.UInt64.of_int 2_000_000_000)
2✔
615
    ; failure_status =
616
        Some
617
          (`Applied
618
            (Account_creation_fees_paid.By_receiver
619
               (Unsigned.UInt64.of_int 1_000_000) ) )
2✔
620
    ; hash = "TXN_1new_HASH"
621
    ; valid_until = None
622
    ; memo = Some "hello"
623
    }
624
  ; { kind = `Payment (* failed payment *)
625
    ; fee_payer = `Pk "Alice"
626
    ; source = `Pk "Alice"
627
    ; token = `Token_id Amount_of.Token_id.default
628
    ; fee_token = `Token_id Amount_of.Token_id.default
629
    ; fee = Unsigned.UInt64.of_int 2_000_000_000
2✔
630
    ; receiver = `Pk "Bob"
631
    ; nonce = Unsigned.UInt32.of_int 3
2✔
632
    ; amount = Some (Unsigned.UInt64.of_int 2_000_000_000)
2✔
633
    ; failure_status = Some (`Failed "Failure")
634
    ; hash = "TXN_1fail_HASH"
635
    ; valid_until = None
636
    ; memo = Some "hello"
637
    }
638
  ; { kind = `Payment (* custom token *)
639
    ; fee_payer = `Pk "Alice"
640
    ; source = `Pk "Alice"
641
    ; token = non_default_token
642
    ; fee = Unsigned.UInt64.of_int 2_000_000_000
2✔
643
    ; receiver = `Pk "Bob"
644
    ; fee_token = `Token_id Amount_of.Token_id.default
645
    ; nonce = Unsigned.UInt32.of_int 3
2✔
646
    ; amount = Some (Unsigned.UInt64.of_int 2_000_000_000)
2✔
647
    ; failure_status = Some (`Applied Account_creation_fees_paid.By_no_one)
648
    ; hash = "TXN_1a_HASH"
649
    ; valid_until = None
650
    ; memo = Some "hello"
651
    }
652
  ; { kind = `Payment (* custom fee-token *)
653
    ; fee_payer = `Pk "Alice"
654
    ; source = `Pk "Alice"
655
    ; token = `Token_id Amount_of.Token_id.default
656
    ; fee = Unsigned.UInt64.of_int 2_000_000_000
2✔
657
    ; receiver = `Pk "Bob"
658
    ; fee_token = non_default_token
659
    ; nonce = Unsigned.UInt32.of_int 3
2✔
660
    ; amount = Some (Unsigned.UInt64.of_int 2_000_000_000)
2✔
661
    ; failure_status = Some (`Applied Account_creation_fees_paid.By_no_one)
662
    ; hash = "TXN_1b_HASH"
663
    ; valid_until = None
664
    ; memo = Some "hello"
665
    }
666
  ; { kind = `Delegation
667
    ; fee_payer = `Pk "Alice"
668
    ; source = `Pk "Alice"
669
    ; token = `Token_id Amount_of.Token_id.default
670
    ; fee_token = `Token_id Amount_of.Token_id.default
671
    ; fee = Unsigned.UInt64.of_int 2_000_000_000
2✔
672
    ; receiver = `Pk "Bob"
673
    ; nonce = Unsigned.UInt32.of_int 3
2✔
674
    ; amount = None
675
    ; failure_status = Some (`Applied Account_creation_fees_paid.By_no_one)
676
    ; hash = "TXN_2_HASH"
677
    ; valid_until = None
678
    ; memo = Some "hello"
679
    }
680
  ]
2✔
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