blob: b4076c657aa78d1a9c342510065ef77b9cfce69d (
plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
|
(* Parallel Nock Execution - Multi-Domain Nock for Multi-Core Urbit!
*
* This is THE breakthrough: Running Nock across multiple CPU cores!
*
* Strategies:
* 1. Parallel batch execution - run multiple Nock computations in parallel
* 2. Parallel scry - read-only queries across domains
* 3. Future: Fork/join within a single Nock computation
*)
(* Parallel execution result *)
type 'a result =
| Success of 'a
| Error of string
(* Execute multiple Nock computations in parallel
*
* Takes a list of (subject, formula) pairs and executes them
* in parallel across the domain pool.
*
* This is perfect for:
* - Batch scry requests
* - Multiple independent pokes
* - Parallel jet execution
*)
let parallel_batch pool computations =
let execute_one (subject, formula) =
try
let result = Nock.nock_on subject formula in
Success result
with
| e -> Error (Printexc.to_string e)
in
Domain_pool.parallel_map pool execute_one computations
(* Execute multiple Nock computations using parallel_for
*
* More efficient for large batches as it uses chunking
*)
let parallel_batch_indexed pool subjects formulas =
let num_tasks = min (List.length subjects) (List.length formulas) in
let results = Domain_pool.parallel_for pool
~start:0
~finish:(num_tasks - 1)
~body:(fun i ->
let subject = List.nth subjects i in
let formula = List.nth formulas i in
try
Success (Nock.nock_on subject formula)
with
| e -> Error (Printexc.to_string e)
)
in
results
(* Parallel scry - execute read-only queries in parallel
*
* This is incredibly powerful for serving many simultaneous queries!
* C Vere can only do one at a time, we can do hundreds simultaneously!
*)
let parallel_scry pool state queries =
let execute_query query =
try
(* In a real implementation, this would use State.peek *)
(* For now, we just run Nock on the state *)
let result = Nock.nock_on state query in
Success result
with
| e -> Error (Printexc.to_string e)
in
Domain_pool.parallel_map pool execute_query queries
(* Map-reduce style parallel Nock
*
* Execute Nock on each item in parallel, then reduce results
*)
let parallel_map_reduce pool ~subjects ~formula ~reduce ~init =
(* Execute Nock in parallel *)
let execute_one subject =
try
Success (Nock.nock_on subject formula)
with
| e -> Error (Printexc.to_string e)
in
let results = Domain_pool.parallel_map pool execute_one subjects in
(* Reduce results *)
List.fold_left (fun acc result ->
match result with
| Success noun -> reduce acc noun
| Error _ -> acc
) init results
(* Async execution - non-blocking Nock
*
* Execute Nock asynchronously and return a promise
*)
let async_nock pool subject formula =
Domain_pool.async pool (fun () ->
try
Success (Nock.nock_on subject formula)
with
| e -> Error (Printexc.to_string e)
)
(* Wait for async result *)
let await_result = Domain_pool.await
(* Benchmark result type *)
type benchmark_result = {
count: int;
sequential_time: float;
parallel_time: float;
speedup: float;
results_match: bool;
}
(* Parallel increment benchmark
*
* Useful for testing parallel speedup
*)
let parallel_increment_bench pool count =
let subjects = List.init count (fun i -> Noun.atom i) in
(* Formula: [4 0 1] (increment subject) *)
let formula = Noun.cell (Noun.atom 4) (Noun.cell (Noun.atom 0) (Noun.atom 1)) in
let start = Unix.gettimeofday () in
let results = List.map (fun subject ->
Nock.nock_on subject formula
) subjects in
let sequential_time = Unix.gettimeofday () -. start in
let start = Unix.gettimeofday () in
let parallel_results_wrapped = Domain_pool.parallel_map pool (fun subject ->
try Success (Nock.nock_on subject formula)
with e -> Error (Printexc.to_string e)
) subjects in
let parallel_time = Unix.gettimeofday () -. start in
(* Extract successful results for comparison *)
let parallel_results = List.filter_map (function
| Success n -> Some n
| Error _ -> None
) parallel_results_wrapped in
let speedup = sequential_time /. parallel_time in
{
count;
sequential_time;
parallel_time;
speedup;
results_match = (results = parallel_results);
}
(* Get parallel execution statistics *)
let stats pool = Domain_pool.stats pool
|