[Git][ghc/ghc][wip/ipe-length] 2 commits: rts/EventLog: Place eliminate duplicate strlens

Ben Gamari (@bgamari) gitlab at gitlab.haskell.org
Wed Dec 13 16:56:52 UTC 2023



Ben Gamari pushed to branch wip/ipe-length at Glasgow Haskell Compiler / GHC


Commits:
c350df3c by Ben Gamari at 2023-12-13T11:56:41-05:00
rts/EventLog: Place eliminate duplicate strlens

Previously many of the `post*` implementations would first compute the
length of the event's strings in order to determine the event length.
Later we would then end up computing the length yet again in
`postString`. Now we instead pass the string length to `postStringLen`,
avoiding the repeated work.

- - - - -
9340d998 by Ben Gamari at 2023-12-13T11:56:41-05:00
rts/eventlog: Place upper bound on IPE string field lengths

The strings in IPE events may be of unbounded length. Limit the lengths
of these fields to 64k characters to ensure that we don't exceed the
maximum event length.

- - - - -


1 changed file:

- rts/eventlog/EventLog.c


Changes:

=====================================
rts/eventlog/EventLog.c
=====================================
@@ -27,6 +27,8 @@
 #include <unistd.h>
 #endif
 
+#define MIN(x,y) ((x) < (y) ? (x) : (y))
+
 Mutex state_change_mutex;
 bool eventlog_enabled; // protected by state_change_mutex to ensure
                        // serialisation of calls to
@@ -85,6 +87,14 @@ bool eventlog_enabled; // protected by state_change_mutex to ensure
  * case is that we must ensure that the buffers of any disabled capabilities are
  * flushed, lest their events are stuck in limbo. This is achieved with a call to
  * flushLocalEventsBuf in traceCapDisable.
+ *
+ *
+ * Note [Maximum event length]
+ * ~~~~~~~~~~~~~~~~~~~~~~~~~~~
+ * The maximum length of an eventlog event is determined by the maximum event
+ * buffer size, EVENT_LOG_SIZE. We must ensure that no variable-length event
+ * exceeds this limit. For this reason we impose maximum length limits on
+ * fields which may have unbounded values.
  */
 
 static const EventLogWriter *event_log_writer = NULL;
@@ -93,6 +103,7 @@ static const EventLogWriter *event_log_writer = NULL;
 // eventlog is restarted
 static eventlog_init_func_t *eventlog_header_funcs = NULL;
 
+// See Note [Maximum event length]
 #define EVENT_LOG_SIZE 2 * (1024 * 1024) // 2MB
 
 static int flushCount = 0;
@@ -172,14 +183,13 @@ static inline void postBuf(EventsBuf *eb, const StgWord8 *buf, uint32_t size)
     eb->pos += size;
 }
 
-/* Post a null-terminated string to the event log.
- * It is the caller's responsibility to ensure that there is
- * enough room for strlen(buf)+1 bytes.
+/* Post a null-terminated string up to a given length to the event log. It is
+ * the caller's responsibility to ensure that there is enough room for
+ * len+1 bytes.
  */
-static inline void postString(EventsBuf *eb, const char *buf)
+static inline void postStringLen(EventsBuf *eb, const char *buf, StgWord len)
 {
     if (buf) {
-        const int len = strlen(buf);
         ASSERT(eb->begin + eb->size > eb->pos + len + 1);
         memcpy(eb->pos, buf, len);
         eb->pos += len;
@@ -188,6 +198,16 @@ static inline void postString(EventsBuf *eb, const char *buf)
     eb->pos++;
 }
 
+/* Post a null-terminated string to the event log.
+ * It is the caller's responsibility to ensure that there is
+ * enough room for strlen(buf)+1 bytes.
+ */
+static inline void postString(EventsBuf *eb, const char *buf)
+{
+    const StgWord len = buf ? strlen(buf) : 0;
+    postStringLen(eb, buf, len);
+}
+
 static inline StgWord64 time_ns(void)
 { return TimeToNS(stat_getElapsedTime()); }
 
@@ -1226,13 +1246,13 @@ void postHeapProfBegin(StgWord8 profile_id)
     postWord8(&eventBuf, profile_id);
     postWord64(&eventBuf, TimeToNS(flags->heapProfileInterval));
     postWord32(&eventBuf, getHeapProfBreakdown());
-    postString(&eventBuf, flags->modSelector);
-    postString(&eventBuf, flags->descrSelector);
-    postString(&eventBuf, flags->typeSelector);
-    postString(&eventBuf, flags->ccSelector);
-    postString(&eventBuf, flags->ccsSelector);
-    postString(&eventBuf, flags->retainerSelector);
-    postString(&eventBuf, flags->bioSelector);
+    postStringLen(&eventBuf, flags->modSelector, modSelector_len);
+    postStringLen(&eventBuf, flags->descrSelector, descrSelector_len);
+    postStringLen(&eventBuf, flags->typeSelector, typeSelector_len);
+    postStringLen(&eventBuf, flags->ccSelector, ccSelector_len);
+    postStringLen(&eventBuf, flags->ccsSelector, ccsSelector_len);
+    postStringLen(&eventBuf, flags->retainerSelector, retainerSelector_len);
+    postStringLen(&eventBuf, flags->bioSelector, bioSelector_len);
     RELEASE_LOCK(&eventBufMutex);
 }
 
@@ -1277,7 +1297,7 @@ void postHeapProfSampleString(StgWord8 profile_id,
     postPayloadSize(&eventBuf, len);
     postWord8(&eventBuf, profile_id);
     postWord64(&eventBuf, residency);
-    postString(&eventBuf, label);
+    postStringLen(&eventBuf, label, label_len);
     RELEASE_LOCK(&eventBufMutex);
 }
 
@@ -1297,9 +1317,9 @@ void postHeapProfCostCentre(StgWord32 ccID,
     postEventHeader(&eventBuf, EVENT_HEAP_PROF_COST_CENTRE);
     postPayloadSize(&eventBuf, len);
     postWord32(&eventBuf, ccID);
-    postString(&eventBuf, label);
-    postString(&eventBuf, module);
-    postString(&eventBuf, srcloc);
+    postStringLen(&eventBuf, label, label_len);
+    postStringLen(&eventBuf, module, module_len);
+    postStringLen(&eventBuf, srcloc, srcloc_len);
     postWord8(&eventBuf, is_caf);
     RELEASE_LOCK(&eventBufMutex);
 }
@@ -1371,17 +1391,20 @@ void postProfBegin(void)
 #if defined(TICKY_TICKY)
 static void postTickyCounterDef(EventsBuf *eb, StgEntCounter *p)
 {
-    StgWord len = 8 + 2 + strlen(p->arg_kinds)+1 + strlen(p->str)+1 + 8 + strlen(p->ticky_json)+1;
+    StgWord arg_kinds_len = strlen(p->arg_kinds);
+    StgWord str_len = strlen(p->str);
+    StgWord ticky_json_len = strlen(p->ticky_json);
+    StgWord len = 8 + 2 + arg_kinds_len+1 + str_len+1 + 8 + ticky_json_len+1;
     CHECK(!ensureRoomForVariableEvent(eb, len));
     postEventHeader(eb, EVENT_TICKY_COUNTER_DEF);
     postPayloadSize(eb, len);
 
     postWord64(eb, (uint64_t)((uintptr_t) p));
     postWord16(eb, (uint16_t) p->arity);
-    postString(eb, p->arg_kinds);
-    postString(eb, p->str);
+    postStringLen(eb, p->arg_kinds, arg_kinds_len);
+    postStringLen(eb, p->str, str_len);
     postWord64(eb, (W_) (INFO_PTR_TO_STRUCT(p->info)));
-    postString(eb, p->ticky_json);
+    postStringLen(eb, p->ticky_json, ticky_json_len);
 
 }
 
@@ -1426,14 +1449,16 @@ void postTickyCounterSamples(StgEntCounter *counters)
 #endif /* TICKY_TICKY */
 void postIPE(const InfoProvEnt *ipe)
 {
+    // See Note [Maximum event length].
+    const StgWord MAX_IPE_STRING_LEN = 65535;
     ACQUIRE_LOCK(&eventBufMutex);
-    StgWord table_name_len = strlen(ipe->prov.table_name);
-    StgWord closure_desc_len = strlen(ipe->prov.closure_desc);
-    StgWord ty_desc_len = strlen(ipe->prov.ty_desc);
-    StgWord label_len = strlen(ipe->prov.label);
-    StgWord module_len = strlen(ipe->prov.module);
-    StgWord src_file_len = strlen(ipe->prov.src_file);
-    StgWord src_span_len = strlen(ipe->prov.src_span);
+    StgWord table_name_len = MIN(strlen(ipe->prov.table_name), MAX_IPE_STRING_LEN);
+    StgWord closure_desc_len = MIN(strlen(ipe->prov.closure_desc), MAX_IPE_STRING_LEN);
+    StgWord ty_desc_len = MIN(strlen(ipe->prov.ty_desc), MAX_IPE_STRING_LEN);
+    StgWord label_len = MIN(strlen(ipe->prov.label), MAX_IPE_STRING_LEN);
+    StgWord module_len = MIN(strlen(ipe->prov.module), MAX_IPE_STRING_LEN);
+    StgWord src_file_len = MIN(strlen(ipe->prov.src_file), MAX_IPE_STRING_LEN);
+    StgWord src_span_len = MIN(strlen(ipe->prov.src_span), MAX_IPE_STRING_LEN);
 
     // 8 for the info word
     // 1 null after each string
@@ -1443,17 +1468,17 @@ void postIPE(const InfoProvEnt *ipe)
     postEventHeader(&eventBuf, EVENT_IPE);
     postPayloadSize(&eventBuf, len);
     postWord64(&eventBuf, (StgWord) INFO_PTR_TO_STRUCT(ipe->info));
-    postString(&eventBuf, ipe->prov.table_name);
-    postString(&eventBuf, ipe->prov.closure_desc);
-    postString(&eventBuf, ipe->prov.ty_desc);
-    postString(&eventBuf, ipe->prov.label);
-    postString(&eventBuf, ipe->prov.module);
+    postStringLen(&eventBuf, ipe->prov.table_name, table_name_len);
+    postStringLen(&eventBuf, ipe->prov.closure_desc, closure_desc_len);
+    postStringLen(&eventBuf, ipe->prov.ty_desc, ty_desc_len);
+    postStringLen(&eventBuf, ipe->prov.label, label_len);
+    postStringLen(&eventBuf, ipe->prov.module, module_len);
 
     // Manually construct the location field: "<file>:<span>\0"
     postBuf(&eventBuf, (const StgWord8*) ipe->prov.src_file, src_file_len);
     StgWord8 colon = ':';
     postBuf(&eventBuf, &colon, 1);
-    postString(&eventBuf, ipe->prov.src_span);
+    postStringLen(&eventBuf, ipe->prov.src_span, src_span_len);
 
     RELEASE_LOCK(&eventBufMutex);
 }



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/498135806715b8c5b775dd468e48a887957c61e2...9340d9987abe2ebf7f66659ffc48a822586f6edd

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/498135806715b8c5b775dd468e48a887957c61e2...9340d9987abe2ebf7f66659ffc48a822586f6edd
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20231213/683a7e84/attachment-0001.html>


More information about the ghc-commits mailing list