Skip to content

Commit 6eee6e3

Browse files
edwintorokMiod Vallat
andcommitted
runtime_events_consumer: harden against corrupted rings
Protect against metadata header getting corrupted, and make a copy at cursor open time. Detect corrupted runtime events rings, check that: * metadata, data and custom offsets are within file bounds * record end is within file bounds * masked offset is within bounds * memcpy is within bounds * ring_size_elements cannot be 0, because then the mask computation is not valid anymore The bounds checks are performed as each entry is processed, to allow processing the maximum number of uncorrupted entries before raising exceptions. Found by ASAN, and (mostly) reproducible with the included testcase. Co-authored-by: Miod Vallat <[email protected]> Signed-off-by: Edwin Török <[email protected]>
1 parent cc326a1 commit 6eee6e3

File tree

2 files changed

+61
-15
lines changed

2 files changed

+61
-15
lines changed

otherlibs/runtime_events/runtime_events_consumer.c

Lines changed: 54 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -367,6 +367,18 @@ void caml_runtime_events_free_cursor(struct caml_runtime_events_cursor *cursor){
367367
}
368368
}
369369

370+
static char* get_map_offset(struct caml_runtime_events_cursor *cursor,
371+
uint64_t offset, int domain_num, uint64_t len)
372+
{
373+
uint64_t limit = cursor->ring_file_size_bytes;
374+
if (offset >= limit)
375+
return NULL;
376+
offset += domain_num * len;
377+
if (offset >= limit || len > limit - offset)
378+
return NULL;
379+
return (char*)cursor->map + offset;
380+
}
381+
370382
runtime_events_error
371383
caml_runtime_events_read_poll(struct caml_runtime_events_cursor *cursor,
372384
void *callback_data, uintnat max_events,
@@ -388,28 +400,49 @@ caml_runtime_events_read_poll(struct caml_runtime_events_cursor *cursor,
388400
return E_CURSOR_POLL_BUSY;
389401
}
390402

403+
if (cursor->metadata.headers_offset > cursor->ring_file_size_bytes
404+
|| !cursor->metadata.ring_size_elements
405+
|| cursor->metadata.ring_size_elements * sizeof(uint64_t)
406+
!= cursor->metadata.ring_size_bytes) {
407+
atomic_store(&cursor->cursor_in_poll, 0);
408+
return E_CORRUPT_STREAM;
409+
}
410+
391411
/* this loop looks a bit odd because we're iterating from the last domain
392412
that we read from on the last read_poll call and then looping around.
393413
This is necessary because in the case where the consumer can't keep up
394414
with message production (i.e max_events is hit each time) it ensures that
395415
messages are read from all domains, rather than just the first. */
396416
for (int i = 0; i < cursor->metadata.max_domains && !early_exit; i++) {
397417
int domain_num = (start_domain + i) % cursor->metadata.max_domains;
418+
uint64_t offset =
419+
cursor->metadata.headers_offset +
420+
domain_num * cursor->metadata.ring_header_size_bytes;
421+
if (offset >= cursor->ring_file_size_bytes
422+
|| offset + cursor->metadata.ring_header_size_bytes
423+
> cursor->ring_file_size_bytes) {
424+
atomic_store(&cursor->cursor_in_poll, 0);
425+
return E_CORRUPT_STREAM;
426+
}
398427

399428
struct runtime_events_buffer_header *runtime_events_buffer_header =
400429
(struct runtime_events_buffer_header *)(
401-
(char*)cursor->map +
402-
cursor->metadata.headers_offset +
403-
domain_num * cursor->metadata.ring_header_size_bytes
430+
get_map_offset(cursor, cursor->metadata.headers_offset,
431+
domain_num,
432+
cursor->metadata.ring_header_size_bytes)
404433
);
405434

406-
uint64_t *ring_ptr = (uint64_t *)((char*)cursor->map +
407-
cursor->metadata.data_offset +
408-
domain_num * cursor->metadata.ring_size_bytes);
435+
uint64_t *ring_ptr =
436+
(uint64_t*)get_map_offset(cursor, cursor->metadata.data_offset,
437+
domain_num, cursor->metadata.ring_size_bytes);
438+
if (!runtime_events_buffer_header || !ring_ptr) {
439+
atomic_store(&cursor->cursor_in_poll, 0);
440+
return E_CORRUPT_STREAM;
441+
}
409442

410443
do {
411444
uint64_t buf[RUNTIME_EVENTS_MAX_MSG_LENGTH];
412-
uint64_t ring_mask, header, msg_length;
445+
uint64_t ring_mask, header, msg_length, ring_masked_pos;
413446
ring_head = atomic_load_acquire(&runtime_events_buffer_header->ring_head);
414447
ring_tail = atomic_load_acquire(&runtime_events_buffer_header->ring_tail);
415448

@@ -430,16 +463,19 @@ caml_runtime_events_read_poll(struct caml_runtime_events_cursor *cursor,
430463
}
431464

432465
ring_mask = cursor->metadata.ring_size_elements - 1;
433-
header = ring_ptr[cursor->current_positions[domain_num] & ring_mask];
466+
ring_masked_pos = cursor->current_positions[domain_num] & ring_mask;
467+
header = ring_ptr[ring_masked_pos];
434468
msg_length = RUNTIME_EVENTS_ITEM_LENGTH(header);
435469

436-
if (msg_length > RUNTIME_EVENTS_MAX_MSG_LENGTH) {
470+
if (msg_length > RUNTIME_EVENTS_MAX_MSG_LENGTH
471+
|| ring_masked_pos + msg_length
472+
> cursor->metadata.ring_size_elements) {
437473
atomic_store(&cursor->cursor_in_poll, 0);
438474
return E_CORRUPT_STREAM;
439475
}
440476

441477
memcpy(buf,
442-
ring_ptr + (cursor->current_positions[domain_num] & ring_mask),
478+
ring_ptr + ring_masked_pos,
443479
msg_length * sizeof(uint64_t));
444480

445481
atomic_thread_fence(memory_order_seq_cst);
@@ -520,6 +556,14 @@ caml_runtime_events_read_poll(struct caml_runtime_events_cursor *cursor,
520556
// User events
521557
uintnat event_id = RUNTIME_EVENTS_ITEM_ID(header);
522558

559+
if (cursor->metadata.custom_events_offset > cursor->ring_file_size_bytes
560+
|| cursor->metadata.custom_events_offset
561+
+ (event_id+1) * sizeof(struct runtime_events_custom_event)
562+
> cursor->ring_file_size_bytes) {
563+
atomic_store(&cursor->cursor_in_poll, 0);
564+
return E_CORRUPT_STREAM;
565+
}
566+
523567
struct runtime_events_custom_event *custom_event =
524568
&((struct runtime_events_custom_event *)
525569
((char *)cursor->map + cursor->metadata.custom_events_offset))

testsuite/tests/lib-runtime-events/test_corrupted.ml

Lines changed: 7 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -62,7 +62,7 @@
6262
let n = Unix.write fd buf 0 (Bytes.length buf) in
6363
assert (n = Bytes.length buf)
6464
in
65-
65+
6666
let write_metadata_header offset value =
6767
let offset = Int64.of_int offset in
6868
let n = Unix.LargeFile.lseek fd offset Unix.SEEK_SET in
@@ -103,7 +103,7 @@
103103
(* now overwrite various fields, corrupting the ring,
104104
and check that we don't crash (raising exceptions is fine).
105105
*)
106-
for offset = 1 to 1 do
106+
for offset = 8 downto 0 do
107107
[0L; size * 3/4 |> Int64.of_int; size * 2 |> Int64.of_int;
108108
Int64.max_int; Int64.min_int; Int64.(shift_right_logical max_int 1)
109109
] |> List.iter @@ fun value ->
@@ -114,16 +114,18 @@
114114
due to bounds error on an earlier offset
115115
*)
116116
Bytes.blit_string original 0 buf 0 (Bytes.length buf);
117-
parse_corrupted path_pid
118117
done;
118+
(* restore metadata header, so we have a valid ring again *)
119+
write_metadata_header 0 1L (* version *);
120+
119121
for is_runtime = 0 to 1 do
120122
for event_type = 0 to 15 (* event type is 4 bits *) do
121123
for event_id = 0 to 64 (* event_id is 13 bits, but not all used yet *) do
122-
for length = 0 to 1 (* short lengths trigger uninit read bugs *) do
124+
for length = 0 to 3 (* short lengths trigger uninit read bugs *) do
123125
(* modify just 1 event in the otherwise valid ring *)
124126
write_event_header is_runtime event_type event_id length;
125127
(* parse ring *)
126-
parse_corrupted path_pid
128+
parse_corrupted path_pid;
127129
done
128130
done
129131
done;

0 commit comments

Comments
 (0)