1 /* -----------------------------------------------------------------------------
2  *
3  * (c) The GHC Team, 2008-2009
4  *
5  * Event log format
6  *
7  * The log format is designed to be extensible: old tools should be
8  * able to parse (but not necessarily understand all of) new versions
9  * of the format, and new tools will be able to understand old log
10  * files.
11  *
12  * Each event has a specific format.  If you add new events, give them
13  * new numbers: we never re-use old event numbers.
14  *
15  * - The format is endian-independent: all values are represented in
16  *    bigendian order.
17  *
18  * - The format is extensible:
19  *
20  *    - The header describes each event type and its length.  Tools
21  *      that don't recognise a particular event type can skip those events.
22  *
23  *    - There is room for extra information in the event type
24  *      specification, which can be ignored by older tools.
25  *
26  *    - Events can have extra information added, but existing fields
27  *      cannot be changed.  Tools should ignore extra fields at the
28  *      end of the event record.
29  *
30  *    - Old event type ids are never re-used; just take a new identifier.
31  *
32  *
33  * The format
34  * ----------
35  *
36  * log : EVENT_HEADER_BEGIN
37  *       EventType*
38  *       EVENT_HEADER_END
39  *       EVENT_DATA_BEGIN
40  *       Event*
41  *       EVENT_DATA_END
42  *
43  * EventType :
44  *       EVENT_ET_BEGIN
45  *       Word16         -- unique identifier for this event
46  *       Int16          -- >=0  size of the event in bytes (minus the header)
47  *                      -- -1   variable size
48  *       Word32         -- length of the next field in bytes
49  *       Word8*         -- string describing the event
50  *       Word32         -- length of the next field in bytes
51  *       Word8*         -- extra info (for future extensions)
52  *       EVENT_ET_END
53  *
54  * Event :
55  *       Word16         -- event_type
56  *       Word64         -- time (nanosecs)
57  *       [Word16]       -- length of the rest (for variable-sized events only)
58  *       ... extra event-specific info ...
59  *
60  *
61  * To add a new event
62  * ------------------
63  *
64  *  - In this file:
65  *    - give it a new number, add a new #define EVENT_XXX below
66  *  - In EventLog.c
67  *    - add it to the EventDesc array
68  *    - emit the event type in initEventLogging()
69  *    - emit the new event in postEvent_()
70  *    - generate the event itself by calling postEvent() somewhere
71  *  - In the Haskell code to parse the event log file:
72  *    - add types and code to read the new event
73  *
74  * -------------------------------------------------------------------------- */
75 
76 #pragma once
77 
78 /*
79  * Markers for begin/end of the Header.
80  */
81 #define EVENT_HEADER_BEGIN    0x68647262 /* 'h' 'd' 'r' 'b' */
82 #define EVENT_HEADER_END      0x68647265 /* 'h' 'd' 'r' 'e' */
83 
84 #define EVENT_DATA_BEGIN      0x64617462 /* 'd' 'a' 't' 'b' */
85 #define EVENT_DATA_END        0xffff
86 
87 /*
88  * Markers for begin/end of the list of Event Types in the Header.
89  * Header, Event Type, Begin = hetb
90  * Header, Event Type, End = hete
91  */
92 #define EVENT_HET_BEGIN       0x68657462 /* 'h' 'e' 't' 'b' */
93 #define EVENT_HET_END         0x68657465 /* 'h' 'e' 't' 'e' */
94 
95 #define EVENT_ET_BEGIN        0x65746200 /* 'e' 't' 'b' 0 */
96 #define EVENT_ET_END          0x65746500 /* 'e' 't' 'e' 0 */
97 
98 /*
99  * Types of event
100  */
101 #define EVENT_CREATE_THREAD        0 /* (thread)               */
102 #define EVENT_RUN_THREAD           1 /* (thread)               */
103 #define EVENT_STOP_THREAD          2 /* (thread, status, blockinfo) */
104 #define EVENT_THREAD_RUNNABLE      3 /* (thread)               */
105 #define EVENT_MIGRATE_THREAD       4 /* (thread, new_cap)      */
106 /* 5, 6, 7 deprecated */
107 #define EVENT_THREAD_WAKEUP        8 /* (thread, other_cap)    */
108 #define EVENT_GC_START             9 /* ()                     */
109 #define EVENT_GC_END              10 /* ()                     */
110 #define EVENT_REQUEST_SEQ_GC      11 /* ()                     */
111 #define EVENT_REQUEST_PAR_GC      12 /* ()                     */
112 /* 13, 14 deprecated */
113 #define EVENT_CREATE_SPARK_THREAD 15 /* (spark_thread)         */
114 #define EVENT_LOG_MSG             16 /* (message ...)          */
115 /* 17 deprecated */
116 #define EVENT_BLOCK_MARKER        18 /* (size, end_time, capability) */
117 #define EVENT_USER_MSG            19 /* (message ...)          */
118 #define EVENT_GC_IDLE             20 /* () */
119 #define EVENT_GC_WORK             21 /* () */
120 #define EVENT_GC_DONE             22 /* () */
121 /* 23, 24 used by eden */
122 #define EVENT_CAPSET_CREATE       25 /* (capset, capset_type)  */
123 #define EVENT_CAPSET_DELETE       26 /* (capset)               */
124 #define EVENT_CAPSET_ASSIGN_CAP   27 /* (capset, cap)          */
125 #define EVENT_CAPSET_REMOVE_CAP   28 /* (capset, cap)          */
126 /* the RTS identifier is in the form of "GHC-version rts_way"  */
127 #define EVENT_RTS_IDENTIFIER      29 /* (capset, name_version_string) */
128 /* the vectors in these events are null separated strings             */
129 #define EVENT_PROGRAM_ARGS        30 /* (capset, commandline_vector)  */
130 #define EVENT_PROGRAM_ENV         31 /* (capset, environment_vector)  */
131 #define EVENT_OSPROCESS_PID       32 /* (capset, pid)          */
132 #define EVENT_OSPROCESS_PPID      33 /* (capset, parent_pid)   */
133 #define EVENT_SPARK_COUNTERS      34 /* (crt,dud,ovf,cnv,gcd,fiz,rem) */
134 #define EVENT_SPARK_CREATE        35 /* ()                     */
135 #define EVENT_SPARK_DUD           36 /* ()                     */
136 #define EVENT_SPARK_OVERFLOW      37 /* ()                     */
137 #define EVENT_SPARK_RUN           38 /* ()                     */
138 #define EVENT_SPARK_STEAL         39 /* (victim_cap)           */
139 #define EVENT_SPARK_FIZZLE        40 /* ()                     */
140 #define EVENT_SPARK_GC            41 /* ()                     */
141 #define EVENT_INTERN_STRING       42 /* (string, id) {not used by ghc} */
142 #define EVENT_WALL_CLOCK_TIME     43 /* (capset, unix_epoch_seconds, nanoseconds) */
143 #define EVENT_THREAD_LABEL        44 /* (thread, name_string)  */
144 #define EVENT_CAP_CREATE          45 /* (cap)                  */
145 #define EVENT_CAP_DELETE          46 /* (cap)                  */
146 #define EVENT_CAP_DISABLE         47 /* (cap)                  */
147 #define EVENT_CAP_ENABLE          48 /* (cap)                  */
148 #define EVENT_HEAP_ALLOCATED      49 /* (heap_capset, alloc_bytes) */
149 #define EVENT_HEAP_SIZE           50 /* (heap_capset, size_bytes) */
150 #define EVENT_HEAP_LIVE           51 /* (heap_capset, live_bytes) */
151 #define EVENT_HEAP_INFO_GHC       52 /* (heap_capset, n_generations,
152                                          max_heap_size, alloc_area_size,
153                                          mblock_size, block_size) */
154 #define EVENT_GC_STATS_GHC        53 /* (heap_capset, generation,
155                                          copied_bytes, slop_bytes, frag_bytes,
156                                          par_n_threads,
157                                          par_max_copied,
158                                          par_tot_copied, par_balanced_copied) */
159 #define EVENT_GC_GLOBAL_SYNC      54 /* ()                     */
160 #define EVENT_TASK_CREATE         55 /* (taskID, cap, tid)       */
161 #define EVENT_TASK_MIGRATE        56 /* (taskID, cap, new_cap)   */
162 #define EVENT_TASK_DELETE         57 /* (taskID)                 */
163 #define EVENT_USER_MARKER         58 /* (marker_name) */
164 #define EVENT_HACK_BUG_T9003      59 /* Hack: see trac #9003 */
165 
166 /* Range 60 - 80 is used by eden for parallel tracing
167  * see http://www.mathematik.uni-marburg.de/~eden/
168  */
169 
170 /* Range 100 - 139 is reserved for Mercury. */
171 
172 /* Range 140 - 159 is reserved for Perf events. */
173 
174 /* Range 160 - 180 is reserved for cost-centre heap profiling events. */
175 
176 #define EVENT_HEAP_PROF_BEGIN              160
177 #define EVENT_HEAP_PROF_COST_CENTRE        161
178 #define EVENT_HEAP_PROF_SAMPLE_BEGIN       162
179 #define EVENT_HEAP_PROF_SAMPLE_COST_CENTRE 163
180 #define EVENT_HEAP_PROF_SAMPLE_STRING      164
181 
182 #define EVENT_USER_BINARY_MSG              181
183 
184 /*
185  * The highest event code +1 that ghc itself emits. Note that some event
186  * ranges higher than this are reserved but not currently emitted by ghc.
187  * This must match the size of the EventDesc[] array in EventLog.c
188  */
189 #define NUM_GHC_EVENT_TAGS        182
190 
191 #if 0  /* DEPRECATED EVENTS: */
192 /* we don't actually need to record the thread, it's implicit */
193 #define EVENT_RUN_SPARK            5 /* (thread)               */
194 #define EVENT_STEAL_SPARK          6 /* (thread, victim_cap)   */
195 /* shutdown replaced by EVENT_CAP_DELETE */
196 #define EVENT_SHUTDOWN             7 /* ()                     */
197 /* ghc changed how it handles sparks so these are no longer applicable */
198 #define EVENT_CREATE_SPARK        13 /* (cap, thread) */
199 #define EVENT_SPARK_TO_THREAD     14 /* (cap, thread, spark_thread) */
200 #define EVENT_STARTUP             17 /* (num_capabilities)     */
201 /* these are used by eden but are replaced by new alternatives for ghc */
202 #define EVENT_VERSION             23 /* (version_string) */
203 #define EVENT_PROGRAM_INVOCATION  24 /* (commandline_string) */
204 #endif
205 
206 /*
207  * Status values for EVENT_STOP_THREAD
208  *
209  * 1-5 are the StgRun return values (from includes/Constants.h):
210  *
211  * #define HeapOverflow   1
212  * #define StackOverflow  2
213  * #define ThreadYielding 3
214  * #define ThreadBlocked  4
215  * #define ThreadFinished 5
216  * #define ForeignCall                  6
217  * #define BlockedOnMVar                7
218  * #define BlockedOnBlackHole           8
219  * #define BlockedOnRead                9
220  * #define BlockedOnWrite               10
221  * #define BlockedOnDelay               11
222  * #define BlockedOnSTM                 12
223  * #define BlockedOnDoProc              13
224  * #define BlockedOnCCall               -- not used (see ForeignCall)
225  * #define BlockedOnCCall_NoUnblockExc  -- not used (see ForeignCall)
226  * #define BlockedOnMsgThrowTo          16
227  */
228 #define THREAD_SUSPENDED_FOREIGN_CALL 6
229 
230 /*
231  * Capset type values for EVENT_CAPSET_CREATE
232  */
233 #define CAPSET_TYPE_CUSTOM      1  /* reserved for end-user applications */
234 #define CAPSET_TYPE_OSPROCESS   2  /* caps belong to the same OS process */
235 #define CAPSET_TYPE_CLOCKDOMAIN 3  /* caps share a local clock/time      */
236 
237 /*
238  * Heap profile breakdown types. See EVENT_HEAP_PROF_BEGIN.
239  */
240 typedef enum {
241     HEAP_PROF_BREAKDOWN_COST_CENTRE = 0x1,
242     HEAP_PROF_BREAKDOWN_MODULE,
243     HEAP_PROF_BREAKDOWN_CLOSURE_DESCR,
244     HEAP_PROF_BREAKDOWN_TYPE_DESCR,
245     HEAP_PROF_BREAKDOWN_RETAINER,
246     HEAP_PROF_BREAKDOWN_BIOGRAPHY,
247     HEAP_PROF_BREAKDOWN_CLOSURE_TYPE
248 } HeapProfBreakdown;
249 
250 #if !defined(EVENTLOG_CONSTANTS_ONLY)
251 
252 typedef StgWord16 EventTypeNum;
253 typedef StgWord64 EventTimestamp; /* in nanoseconds */
254 typedef StgWord32 EventThreadID;
255 typedef StgWord16 EventCapNo;
256 typedef StgWord16 EventPayloadSize; /* variable-size events */
257 typedef StgWord16 EventThreadStatus; /* status for EVENT_STOP_THREAD */
258 typedef StgWord32 EventCapsetID;
259 typedef StgWord16 EventCapsetType;   /* types for EVENT_CAPSET_CREATE */
260 typedef StgWord64 EventTaskId;         /* for EVENT_TASK_* */
261 typedef StgWord64 EventKernelThreadId; /* for EVENT_TASK_CREATE */
262 
263 #define EVENT_PAYLOAD_SIZE_MAX STG_WORD16_MAX
264 #endif
265