summaryrefslogtreecommitdiff
path: root/ocaml/lib/noun.ml
diff options
context:
space:
mode:
Diffstat (limited to 'ocaml/lib/noun.ml')
-rw-r--r--ocaml/lib/noun.ml48
1 files changed, 48 insertions, 0 deletions
diff --git a/ocaml/lib/noun.ml b/ocaml/lib/noun.ml
index 9be65b7..f706dca 100644
--- a/ocaml/lib/noun.ml
+++ b/ocaml/lib/noun.ml
@@ -86,6 +86,54 @@ let inc = function
| Atom n -> Atom (Z.succ n)
| Cell _ -> raise Exit
+(** Compute mug (31-bit hash) of a noun
+
+ This implements Urbit's mug hash function using FNV-1a.
+ The mug is cached in the C implementation but we compute it fresh each time.
+
+ For atoms: hash the bytes of the integer representation
+ For cells: mix the mugs of head and tail
+*)
+let rec mug noun =
+ (* FNV-1a constants - using hex to avoid signed int32 overflow *)
+ let fnv_prime = 16777619l in
+ let fnv_basis = 0x811c9dc5l in (* 2166136261 in decimal *)
+
+ (* Mask to 31 bits (Urbit uses 31-bit mugs) *)
+ let mask31 x = Int32.logand x 0x7fffffffl in
+
+ (* Hash bytes using FNV-1a *)
+ let hash_bytes bytes =
+ let len = Bytes.length bytes in
+ let rec loop i hash =
+ if i >= len then hash
+ else
+ let byte = Int32.of_int (Bytes.get_uint8 bytes i) in
+ let hash' = Int32.mul (Int32.logxor hash byte) fnv_prime in
+ loop (i + 1) hash'
+ in
+ mask31 (loop 0 fnv_basis)
+ in
+
+ (* Mix two mugs together (for cells) *)
+ let mix_mugs a_mug b_mug =
+ (* Mix by XOR and multiply, then mask *)
+ let mixed = Int32.mul (Int32.logxor a_mug b_mug) fnv_prime in
+ mask31 mixed
+ in
+
+ match noun with
+ | Atom z ->
+ (* Convert atom to bytes and hash *)
+ let bytes = Z.to_bits z in
+ hash_bytes (Bytes.of_string bytes)
+
+ | Cell (h, t) ->
+ (* Mix the mugs of head and tail *)
+ let h_mug = mug h in
+ let t_mug = mug t in
+ mix_mugs h_mug t_mug
+
(** Pretty-print a noun *)
let rec pp_noun fmt = function
| Atom n -> Format.fprintf fmt "%s" (Z.to_string n)