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

MinaProtocol / mina / 2993

20 Nov 2024 02:52PM UTC coverage: 30.633% (-30.3%) from 60.94%
2993

push

buildkite

web-flow
Merge pull request #16331 from MinaProtocol/dkijania/remove_terraform_files

[Int tests] remove terraform , cloud engine and update README.md

20171 of 65848 relevant lines covered (30.63%)

8642.23 hits per line

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

36.81
/src/lib/sparse_ledger_lib/sparse_ledger.ml
1
open Core_kernel
9✔
2

3
module Tree = struct
4
  [%%versioned
5
  module Stable = struct
6
    [@@@no_toplevel_latest_type]
7

8
    module V1 = struct
9
      type ('hash, 'account) t =
13✔
10
        | Account of 'account
×
11
        | Hash of 'hash
×
12
        | Node of 'hash * ('hash, 'account) t * ('hash, 'account) t
×
13
      [@@deriving equal, sexp, yojson]
27✔
14

15
      let rec to_latest acct_to_latest = function
16
        | Account acct ->
×
17
            Account (acct_to_latest acct)
×
18
        | Hash hash ->
×
19
            Hash hash
20
        | Node (hash, l, r) ->
×
21
            Node (hash, to_latest acct_to_latest l, to_latest acct_to_latest r)
×
22
    end
23
  end]
24

25
  type ('hash, 'account) t = ('hash, 'account) Stable.Latest.t =
×
26
    | Account of 'account
×
27
    | Hash of 'hash
×
28
    | Node of 'hash * ('hash, 'account) t * ('hash, 'account) t
×
29
  [@@deriving equal, sexp, yojson]
×
30
end
31

32
module T = struct
33
  [%%versioned
34
  module Stable = struct
35
    [@@@no_toplevel_latest_type]
36

37
    module V2 = struct
38
      type ('hash, 'key, 'account) t =
22✔
39
        { indexes : ('key * int) list
×
40
        ; depth : int
×
41
        ; tree : ('hash, 'account) Tree.Stable.V1.t
×
42
        }
43
      [@@deriving sexp, yojson]
45✔
44
    end
45
  end]
46

47
  type ('hash, 'key, 'account) t = ('hash, 'key, 'account) Stable.Latest.t =
×
48
    { indexes : ('key * int) list
×
49
    ; depth : int
×
50
    ; tree : ('hash, 'account) Tree.t
×
51
    }
52
  [@@deriving sexp, yojson]
×
53
end
54

55
module type S = sig
56
  type hash
57

58
  type account_id
59

60
  type account
61

62
  type t = (hash, account_id, account) T.t [@@deriving sexp, yojson]
63

64
  val of_hash : depth:int -> hash -> t
65

66
  val get_exn : t -> int -> account
67

68
  val path_exn : t -> int -> [ `Left of hash | `Right of hash ] list
69

70
  val set_exn : t -> int -> account -> t
71

72
  val find_index_exn : t -> account_id -> int
73

74
  val add_path :
75
    t -> [ `Left of hash | `Right of hash ] list -> account_id -> account -> t
76

77
  (** Same as [add_path], but using the hashes provided in the wide merkle path
78
      instead of recomputing them.
79
      This is unsafe: the hashes are not checked or recomputed.
80
  *)
81
  val add_wide_path_unsafe :
82
       t
83
    -> [ `Left of hash * hash | `Right of hash * hash ] list
84
    -> account_id
85
    -> account
86
    -> t
87

88
  val iteri : t -> f:(int -> account -> unit) -> unit
89

90
  val merkle_root : t -> hash
91

92
  val depth : t -> int
93
end
94

95
let tree { T.tree; _ } = tree
×
96

97
let of_hash ~depth h = { T.indexes = []; depth; tree = Hash h }
2,298✔
98

99
module Make (Hash : sig
100
  type t [@@deriving equal, sexp, yojson, compare]
101

102
  val merge : height:int -> t -> t -> t
103
end) (Account_id : sig
104
  type t [@@deriving equal, sexp, yojson]
105
end) (Account : sig
106
  type t [@@deriving equal, sexp, yojson]
107

108
  val data_hash : t -> Hash.t
109
end) : sig
110
  include
111
    S
112
      with type hash := Hash.t
113
       and type account_id := Account_id.t
114
       and type account := Account.t
115

116
  val hash : (Hash.t, Account.t) Tree.t -> Hash.t
117
end = struct
118
  type t = (Hash.t, Account_id.t, Account.t) T.t [@@deriving sexp, yojson]
×
119

120
  let of_hash ~depth (hash : Hash.t) = of_hash ~depth hash
2,298✔
121

122
  let hash : (Hash.t, Account.t) Tree.t -> Hash.t = function
123
    | Account a ->
424✔
124
        Account.data_hash a
125
    | Hash h ->
214✔
126
        h
127
    | Node (h, _, _) ->
3,684✔
128
        h
129

130
  type index = int [@@deriving sexp, yojson]
×
131

132
  let depth { T.depth; _ } = depth
×
133

134
  let merkle_root { T.tree; _ } = hash tree
2,678✔
135

136
  let add_path_impl ~replace_self tree0 path0 account =
137
    (* Takes height, left and right children and builds a pair of sibling nodes
138
       one level up *)
139
    let build_tail_f height (prev_l, prev_r) =
4,576✔
140
      replace_self ~f:(fun mself ->
23,074✔
141
          let self =
23,074✔
142
            match mself with
143
            | Some self ->
22,892✔
144
                self
145
            | None ->
182✔
146
                Hash.merge ~height (hash prev_l) (hash prev_r)
182✔
147
          in
148
          Tree.Node (self, prev_l, prev_r) )
149
    in
150
    (* Builds the tail of path, i.e. part of the path that is not present in
151
       the current ledger and we just add it all the way down to account
152
       using the path *)
153
    let build_tail hash_node_to_bottom_path =
154
      let bottom_el, bottom_to_hash_node_path =
4,160✔
155
        Mina_stdlib.Nonempty_list.(rev hash_node_to_bottom_path |> uncons)
4,160✔
156
      in
157
      (* Left and right branches of a node that is parent of the bottom node *)
158
      let init = replace_self ~f:(Fn.const (Tree.Account account)) bottom_el in
4,160✔
159
      List.foldi ~init bottom_to_hash_node_path ~f:build_tail_f
4,160✔
160
    in
161
    (* Traverses the tree along path, collecting nodes and untraversed sibling hashes
162
        Stops when encounters `Hash` or `Account` node.
163

164
       Returns the last visited node (`Hash` or `Account`), remainder of path and
165
       collected node/sibling hashes in bottom-to-top order.
166
    *)
167
    let rec traverse_through_nodes = function
168
      | Tree.Account _, _ :: _ ->
×
169
          failwith "path is longer than a tree's branch"
170
      | Account _, [] | Tree.Hash _, [] ->
108✔
171
          Tree.Account account
172
      | Tree.Hash h, fst_el :: rest ->
4,160✔
173
          let tail_l, tail_r =
174
            build_tail (Mina_stdlib.Nonempty_list.init fst_el rest)
4,160✔
175
          in
176
          Tree.Node (h, tail_l, tail_r)
4,160✔
177
      | Node (h, l, r), `Left _ :: rest ->
13,362✔
178
          Tree.Node (h, traverse_through_nodes (l, rest), r)
13,362✔
179
      | Node (h, l, r), `Right _ :: rest ->
2,668✔
180
          Tree.Node (h, l, traverse_through_nodes (r, rest))
2,668✔
181
      | Node _, [] ->
×
182
          failwith "path is shorter than a tree's branch"
183
    in
184
    traverse_through_nodes (tree0, List.rev path0)
4,576✔
185

186
  let add_path (t : t) path account_id account =
187
    let index =
416✔
188
      List.foldi path ~init:0 ~f:(fun i acc x ->
189
          match x with `Right _ -> acc + (1 lsl i) | `Left _ -> acc )
832✔
190
    in
191
    let replace_self ~f = function
416✔
192
      | `Left h_r ->
390✔
193
          (f None, Tree.Hash h_r)
390✔
194
      | `Right h_l ->
×
195
          (Tree.Hash h_l, f None)
×
196
    in
197
    { t with
198
      tree = add_path_impl ~replace_self t.tree path account
416✔
199
    ; indexes = (account_id, index) :: t.indexes
200
    }
201

202
  let add_wide_path_unsafe (t : t) path account_id account =
203
    let index =
4,160✔
204
      List.foldi path ~init:0 ~f:(fun i acc x ->
205
          match x with `Right _ -> acc + (1 lsl i) | `Left _ -> acc )
6,336✔
206
    in
207
    let replace_self ~f = function
4,160✔
208
      | `Left (h_l, h_r) ->
22,344✔
209
          (f (Some h_l), Tree.Hash h_r)
22,344✔
210
      | `Right (h_l, h_r) ->
4,500✔
211
          (Tree.Hash h_l, f (Some h_r))
4,500✔
212
    in
213
    { t with
214
      tree = add_path_impl ~replace_self t.tree path account
4,160✔
215
    ; indexes = (account_id, index) :: t.indexes
216
    }
217

218
  let iteri (t : t) ~f =
219
    let rec go acc i tree ~f =
×
220
      match tree with
×
221
      | Tree.Account a ->
×
222
          f acc a
223
      | Hash _ ->
×
224
          ()
225
      | Node (_, l, r) ->
×
226
          go acc (i - 1) l ~f ;
227
          go (acc + (1 lsl i)) (i - 1) r ~f
×
228
    in
229
    go 0 (t.depth - 1) t.tree ~f
230

231
  let ith_bit idx i = (idx lsr i) land 1 = 1
4,240✔
232

233
  let find_index_exn (t : t) aid =
234
    match List.Assoc.find t.indexes ~equal:Account_id.equal aid with
900✔
235
    | Some x ->
900✔
236
        x
237
    | None ->
×
238
        failwithf
239
          !"Sparse_ledger.find_index_exn: %{sexp:Account_id.t} not in %{sexp: \
×
240
            Account_id.t list}"
241
          aid
242
          (List.map t.indexes ~f:fst)
×
243
          ()
244

245
  let get_exn ({ T.tree; depth; _ } as t) idx =
246
    let rec go i tree =
900✔
247
      match (i < 0, tree) with
4,500✔
248
      | true, Tree.Account acct ->
900✔
249
          acct
250
      | false, Node (_, l, r) ->
3,600✔
251
          let go_right = ith_bit idx i in
252
          if go_right then go (i - 1) r else go (i - 1) l
1,040✔
253
      | _ ->
×
254
          let expected_kind = if i < 0 then "n account" else " node" in
×
255
          let kind =
256
            match tree with
257
            | Account _ ->
×
258
                "n account"
259
            | Hash _ ->
×
260
                " hash"
261
            | Node _ ->
×
262
                " node"
263
          in
264
          failwithf
265
            !"Sparse_ledger.get: Bad index %i. Expected a%s, but got a%s at \
×
266
              depth %i. Tree = %{sexp:t}, tree_depth = %d"
267
            idx expected_kind kind (depth - i) t depth ()
268
    in
269
    go (depth - 1) tree
270

271
  let set_exn (t : t) idx acct =
272
    let rec go i tree =
160✔
273
      match (i < 0, tree) with
800✔
274
      | true, Tree.Account _ ->
160✔
275
          Tree.Account acct
276
      | false, Node (_, l, r) ->
640✔
277
          let l, r =
278
            let go_right = ith_bit idx i in
279
            if go_right then (l, go (i - 1) r) else (go (i - 1) l, r)
160✔
280
          in
281
          Node (Hash.merge ~height:i (hash l) (hash r), l, r)
640✔
282
      | _ ->
×
283
          let expected_kind = if i < 0 then "n account" else " node" in
×
284
          let kind =
285
            match tree with
286
            | Account _ ->
×
287
                "n account"
288
            | Hash _ ->
×
289
                " hash"
290
            | Node _ ->
×
291
                " node"
292
          in
293
          failwithf
294
            "Sparse_ledger.set: Bad index %i. Expected a%s, but got a%s at \
295
             depth %i."
296
            idx expected_kind kind (t.depth - i) ()
297
    in
298
    { t with tree = go (t.depth - 1) t.tree }
160✔
299

300
  let path_exn { T.tree; depth; _ } idx =
301
    let rec go acc i tree =
×
302
      if i < 0 then acc
×
303
      else
304
        match tree with
×
305
        | Tree.Account _ ->
×
306
            failwithf "Sparse_ledger.path: Bad depth at index %i." idx ()
307
        | Hash _ ->
×
308
            failwithf "Sparse_ledger.path: Dead end at index %i." idx ()
309
        | Node (_, l, r) ->
×
310
            let go_right = ith_bit idx i in
311
            if go_right then go (`Right (hash l) :: acc) (i - 1) r
×
312
            else go (`Left (hash r) :: acc) (i - 1) l
×
313
    in
314
    go [] (depth - 1) tree
315
end
316

317
type ('hash, 'key, 'account) t = ('hash, 'key, 'account) T.t [@@deriving yojson]
×
318

319
let%test_module "sparse-ledger-test" =
320
  ( module struct
321
    module Hash = struct
322
      type t = Core_kernel.Md5.t [@@deriving sexp, compare]
×
323

324
      let equal h1 h2 = Int.equal (compare h1 h2) 0
×
325

326
      let to_yojson md5 = `String (Core_kernel.Md5.to_hex md5)
×
327

328
      let of_yojson = function
329
        | `String x ->
×
330
            Or_error.try_with (fun () -> Core_kernel.Md5.of_hex_exn x)
×
331
            |> Result.map_error ~f:Error.to_string_hum
332
        | _ ->
×
333
            Error "Expected a hex-encoded MD5 hash"
334

335
      let merge ~height x y =
336
        let open Md5 in
×
337
        digest_string
338
          (sprintf "sparse-ledger_%03d" height ^ to_binary x ^ to_binary y)
×
339

340
      let gen =
341
        Quickcheck.Generator.map String.quickcheck_generator
×
342
          ~f:Md5.digest_string
343
    end
344

345
    module Account = struct
346
      module T = struct
347
        type t =
×
348
          { name : Bounded_types.String.Stable.V1.t; favorite_number : int }
×
349
        [@@deriving bin_io, equal, sexp, yojson]
×
350
      end
351

352
      include T
353

354
      let key { name; _ } = name
×
355

356
      let data_hash t = Md5.digest_string (Binable.to_string (module T) t)
×
357

358
      let gen =
359
        let open Quickcheck.Generator.Let_syntax in
360
        let%map name = String.quickcheck_generator
361
        and favorite_number = Int.quickcheck_generator in
362
        { name; favorite_number }
×
363
    end
364

365
    module Account_id = struct
366
      type t = string [@@deriving sexp, equal, yojson]
×
367
    end
368

369
    include Make (Hash) (Account_id) (Account)
370

371
    let gen =
372
      let open Quickcheck.Generator in
373
      let open Let_syntax in
374
      let indexes max_depth t =
375
        let rec go addr d = function
×
376
          | Tree.Account a ->
×
377
              [ (Account.key a, addr) ]
×
378
          | Hash _ ->
×
379
              []
380
          | Node (_, l, r) ->
×
381
              go addr (d - 1) l @ go (addr lor (1 lsl d)) (d - 1) r
×
382
        in
383
        go 0 (max_depth - 1) t
384
      in
385
      let rec prune_hash_branches = function
386
        | Tree.Hash h ->
×
387
            Tree.Hash h
388
        | Account a ->
×
389
            Account a
390
        | Node (h, l, r) -> (
×
391
            match (prune_hash_branches l, prune_hash_branches r) with
×
392
            | Hash _, Hash _ ->
×
393
                Hash h
394
            | l, r ->
×
395
                Node (h, l, r) )
396
      in
397
      let rec gen depth =
398
        if depth = 0 then Account.gen >>| fun a -> Tree.Account a
×
399
        else
400
          let t =
×
401
            let sub = gen (depth - 1) in
402
            let%map l = sub and r = sub in
403
            Tree.Node (Hash.merge ~height:(depth - 1) (hash l) (hash r), l, r)
×
404
          in
405
          weighted_union
406
            [ (1. /. 3., Hash.gen >>| fun h -> Tree.Hash h); (2. /. 3., t) ]
×
407
      in
408
      let%bind depth = Int.gen_incl 0 16 in
×
409
      let%map tree = gen depth >>| prune_hash_branches in
×
410
      { T.tree; depth; indexes = indexes depth tree }
×
411

412
    let%test_unit "iteri consistent indices with t.indexes" =
413
      Quickcheck.test gen ~f:(fun t ->
×
414
          let indexes = Int.Set.of_list (t.indexes |> List.map ~f:snd) in
×
415
          iteri t ~f:(fun i _ ->
×
416
              [%test_result: bool]
×
417
                ~message:
418
                  "Iteri index should be contained in the indexes auxillary \
419
                   structure"
420
                ~expect:true (Int.Set.mem indexes i) ) )
×
421

422
    let%test_unit "path_test" =
423
      Quickcheck.test gen ~f:(fun t ->
×
424
          let root = { t with indexes = []; tree = Hash (merkle_root t) } in
×
425
          let t' =
426
            List.fold t.indexes ~init:root ~f:(fun acc (_, index) ->
427
                let account = get_exn t index in
×
428
                add_path acc (path_exn t index) (Account.key account) account )
×
429
          in
430
          assert (Tree.equal Hash.equal Account.equal t'.tree t.tree) )
×
431
  end )
18✔
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

© 2025 Coveralls, Inc