summaryrefslogtreecommitdiff
path: root/ocaml/test/test_clay.ml
blob: 8312f05d2e73731c88a25e8e47f8c3c129aaf866 (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
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
(* Test Clay Filesystem Driver *)

open Io_drivers

let test_clay_creation _env =
  Printf.printf "Test: Clay driver creation...\n";

  let config = Clay.{
    pier_path = "/tmp/test_clay_pier";
  } in

  let clay = Clay.create config in
  let stats = Clay.get_stats clay in

  Printf.printf "  Created Clay driver for pier: %s\n" config.pier_path;
  Printf.printf "  Initial stats - files read: %Ld, written: %Ld\n"
    stats.files_read stats.files_written;

  assert (stats.files_read = 0L);
  assert (stats.files_written = 0L);

  Printf.printf "  ✓ Clay driver creation works!\n\n"

let test_file_read_write env =
  Printf.printf "Test: File read/write...\n";

  let config = Clay.{
    pier_path = "/tmp/test_clay_pier";
  } in

  let clay = Clay.create config in

  (* Write a file *)
  let test_data = Bytes.of_string "Hello, Clay! This is a test file." in

  (match Clay.write_file clay ~env "test.txt" test_data with
   | Clay.Success () ->
       Printf.printf "  Wrote test file\n"
   | Clay.Error e ->
       Printf.printf "  ERROR writing: %s\n" e;
       assert false
  );

  (* Read it back *)
  (match Clay.read_file clay ~env "test.txt" with
   | Clay.Success data ->
       Printf.printf "  Read test file (%d bytes)\n" (Bytes.length data);
       assert (data = test_data);
       Printf.printf "  ✓ Data matches!\n"
   | Clay.Error e ->
       Printf.printf "  ERROR reading: %s\n" e;
       assert false
  );

  (* Check stats *)
  let stats = Clay.get_stats clay in
  Printf.printf "  Stats - read: %Ld, written: %Ld, bytes read: %Ld, bytes written: %Ld\n"
    stats.files_read stats.files_written stats.bytes_read stats.bytes_written;

  assert (stats.files_read = 1L);
  assert (stats.files_written = 1L);

  Printf.printf "  ✓ File read/write works!\n\n"

let test_directory_operations env =
  Printf.printf "Test: Directory operations...\n";

  let config = Clay.{
    pier_path = "/tmp/test_clay_pier";
  } in

  let clay = Clay.create config in

  (* Create some test files in a directory *)
  let test_files = [
    ("subdir/file1.txt", "Content 1");
    ("subdir/file2.txt", "Content 2");
    ("subdir/file3.txt", "Content 3");
  ] in

  List.iter (fun (path, content) ->
    match Clay.write_file clay ~env path (Bytes.of_string content) with
    | Clay.Success () -> ()
    | Clay.Error e ->
        Printf.printf "  ERROR: %s\n" e;
        assert false
  ) test_files;

  Printf.printf "  Created %d test files in subdir/\n" (List.length test_files);

  (* List directory *)
  (match Clay.list_directory clay ~env "subdir" with
   | Clay.Success entries ->
       Printf.printf "  Directory listing (%d entries):\n" (List.length entries);
       List.iter (fun entry ->
         Printf.printf "    - %s\n" entry
       ) entries;

       assert (List.length entries = 3);
       Printf.printf "  ✓ All files found!\n"

   | Clay.Error e ->
       Printf.printf "  ERROR listing directory: %s\n" e;
       assert false
  );

  Printf.printf "  ✓ Directory operations work!\n\n"

let test_parallel_operations env =
  Printf.printf "Test: Parallel file operations (THE SPEEDUP!)...\n";

  Eio.Switch.run @@ fun sw ->

  let config = Clay.{
    pier_path = "/tmp/test_clay_pier";
  } in

  let clay = Clay.create config in

  (* Create many test files to demonstrate parallel I/O *)
  let num_files = 50 in
  Printf.printf "  Creating %d test files for parallel operations...\n" num_files;

  let test_files = List.init num_files (fun i ->
    let path = Printf.sprintf "parallel/file_%03d.txt" i in
    let content = Printf.sprintf "This is test file number %d with some content" i in
    (path, Bytes.of_string content)
  ) in

  (* Sequential write for comparison *)
  Printf.printf "\n  Sequential write test:\n";
  let seq_start = Unix.gettimeofday () in
  List.iter (fun (path, data) ->
    match Clay.write_file clay ~env path data with
    | Clay.Success () -> ()
    | Clay.Error _ -> ()
  ) test_files;
  let seq_time = Unix.gettimeofday () -. seq_start in
  Printf.printf "    Wrote %d files in %.4fs (%.0f files/sec)\n"
    num_files seq_time (float_of_int num_files /. seq_time);

  (* Parallel write - THE INNOVATION! *)
  Printf.printf "\n  Parallel write test:\n";
  let par_start = Unix.gettimeofday () in
  let _ = Clay.parallel_write clay ~env ~sw test_files in
  let par_time = Unix.gettimeofday () -. par_start in

  let speedup = seq_time /. par_time in
  Printf.printf "    💥 SPEEDUP: %.2fx faster than sequential!\n" speedup;

  (* Parallel read test *)
  Printf.printf "\n  Parallel read test:\n";
  let paths = List.map fst test_files in
  let results = Clay.parallel_read clay ~env ~sw paths in

  Printf.printf "    Successfully read %d/%d files\n"
    (List.length results) (List.length paths);

  let stats = Clay.get_stats clay in
  Printf.printf "\n  Final stats:\n";
  Printf.printf "    Files read: %Ld\n" stats.files_read;
  Printf.printf "    Files written: %Ld\n" stats.files_written;
  Printf.printf "    Bytes read: %Ld\n" stats.bytes_read;
  Printf.printf "    Bytes written: %Ld\n" stats.bytes_written;

  Printf.printf "  ✓ Parallel operations work (and are FAST!)!\n\n"

let test_batch_copy env =
  Printf.printf "Test: Batch copy operations...\n";

  Eio.Switch.run @@ fun sw ->

  let config = Clay.{
    pier_path = "/tmp/test_clay_pier";
  } in

  let clay = Clay.create config in

  (* Create source files *)
  let source_files = List.init 10 (fun i ->
    Printf.sprintf "batch_src/file_%d.txt" i
  ) in

  List.iter (fun path ->
    let content = Bytes.of_string (Printf.sprintf "Content of %s" path) in
    match Clay.write_file clay ~env path content with
    | Clay.Success () -> ()
    | Clay.Error _ -> ()
  ) source_files;

  Printf.printf "  Created %d source files\n" (List.length source_files);

  (* Batch copy *)
  (match Clay.batch_copy clay ~env ~sw source_files "batch_dest" with
   | Clay.Success count ->
       Printf.printf "  Copied %d files in batch\n" count;
       assert (count = List.length source_files)
   | Clay.Error e ->
       Printf.printf "  ERROR: %s\n" e;
       assert false
  );

  Printf.printf "  ✓ Batch copy works!\n\n"

let test_recursive_scan env =
  Printf.printf "Test: Recursive directory scan...\n";

  let config = Clay.{
    pier_path = "/tmp/test_clay_pier";
  } in

  let clay = Clay.create config in

  (* Scan entire pier *)
  let all_files = Clay.scan_directory clay ~env "" in

  Printf.printf "  Found %d files total in pier\n" (List.length all_files);
  Printf.printf "  First 10 files:\n";
  List.iteri (fun i file ->
    if i < 10 then Printf.printf "    %s\n" file
  ) all_files;

  Printf.printf "  ✓ Recursive scan works!\n\n"

let () =
  Printf.printf "\n🚀🚀🚀 === CLAY FILESYSTEM TESTS === 🚀🚀🚀\n\n";

  Eio_main.run @@ fun env ->
  test_clay_creation env;
  test_file_read_write env;
  test_directory_operations env;
  test_parallel_operations env;
  test_batch_copy env;
  test_recursive_scan env;

  Printf.printf "🎉🎉🎉 === ALL CLAY TESTS PASSED! === 🎉🎉🎉\n\n";
  Printf.printf "Clay filesystem driver is working!\n";
  Printf.printf "- Async file read/write ✓\n";
  Printf.printf "- Directory operations ✓\n";
  Printf.printf "- PARALLEL file I/O (MASSIVE SPEEDUP!) ✓\n";
  Printf.printf "- Batch copy operations ✓\n";
  Printf.printf "- Recursive directory scanning ✓\n";
  Printf.printf "\n💥 C Vere blocking I/O < Overe async parallel I/O! 💥\n"