File 2462-seq_trace-Inherit-trace-token-on-spawn.patch of Package erlang

From 2f75782815441a161e6157c941b7f482f96bdbcb Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?John=20H=C3=B6gberg?= <john@erlang.org>
Date: Tue, 19 Mar 2019 17:39:14 +0100
Subject: [PATCH 2/3] seq_trace: Inherit trace token on spawn

Trace tokens can be lost when a process delegates message sending
to a child process, which is pretty surprising and limits the
usefulness of seq tracing. One example of this is gen_statem:call/4
which uses a child process to implement timeouts without the risk
of a late message arriving to the caller.

This commit attempts to remedy this by propagating the trace token
to spawned processes, and adds optional tracing for process
spawning as well.
---
 erts/emulator/beam/bif.c                |  2 +-
 erts/emulator/beam/dist.c               |  6 +-
 erts/emulator/beam/erl_bif_trace.c      | 13 +++--
 erts/emulator/beam/erl_message.c        |  2 +-
 erts/emulator/beam/erl_nif.c            |  2 +-
 erts/emulator/beam/erl_proc_sig_queue.c |  2 +-
 erts/emulator/beam/erl_process.c        | 42 +++++++++++++-
 erts/emulator/beam/erl_process.h        |  2 +
 erts/emulator/beam/erl_trace.c          |  3 +-
 erts/emulator/beam/erl_trace.h          |  4 +-
 lib/kernel/doc/src/seq_trace.xml        | 55 +++++++++++++-----
 lib/kernel/src/seq_trace.erl            | 20 ++++---
 lib/kernel/test/seq_trace_SUITE.erl     | 98 +++++++++++++++++++++++++++++----
 lib/observer/test/ttb_SUITE.erl         | 10 ++--
 14 files changed, 208 insertions(+), 53 deletions(-)

diff --git a/erts/emulator/beam/bif.c b/erts/emulator/beam/bif.c
index c102ddbee6..21352ec844 100644
--- a/erts/emulator/beam/bif.c
+++ b/erts/emulator/beam/bif.c
@@ -1987,7 +1987,7 @@ do_send(Process *p, Eterm to, Eterm msg, Eterm return_term, Eterm *refp,
                 trace_send(p, portid, msg);
 
             if (have_seqtrace(SEQ_TRACE_TOKEN(p))) {
-                seq_trace_update_send(p);
+                seq_trace_update_serial(p);
                 seq_trace_output(SEQ_TRACE_TOKEN(p), msg,
                                  SEQ_TRACE_SEND, portid, p);
             }
diff --git a/erts/emulator/beam/dist.c b/erts/emulator/beam/dist.c
index b50c8273b1..4a3dc957a9 100644
--- a/erts/emulator/beam/dist.c
+++ b/erts/emulator/beam/dist.c
@@ -1100,7 +1100,7 @@ erts_dsig_send_msg(ErtsDSigSendContext* ctx, Eterm remote, Eterm message)
 #endif
 
     if (have_seqtrace(SEQ_TRACE_TOKEN(sender))) {
-	seq_trace_update_send(sender);
+	seq_trace_update_serial(sender);
 	token = SEQ_TRACE_TOKEN(sender);
 	seq_trace_output(token, message, SEQ_TRACE_SEND, remote, sender);
     }
@@ -1174,7 +1174,7 @@ erts_dsig_send_reg_msg(ErtsDSigSendContext* ctx, Eterm remote_name, Eterm messag
 #endif
 
     if (have_seqtrace(SEQ_TRACE_TOKEN(sender))) {
-	seq_trace_update_send(sender);
+	seq_trace_update_serial(sender);
 	token = SEQ_TRACE_TOKEN(sender);
 	seq_trace_output(token, message, SEQ_TRACE_SEND, remote_name, sender);
     }
@@ -1233,7 +1233,7 @@ erts_dsig_send_exit_tt(ErtsDSigSendContext *ctx, Eterm local, Eterm remote,
 
     UseTmpHeapNoproc(6);
     if (have_seqtrace(token)) {
-	seq_trace_update_send(dsdp->proc);
+	seq_trace_update_serial(dsdp->proc);
 	seq_trace_output_exit(token, reason, SEQ_TRACE_SEND, remote, local);
 	ctl = TUPLE5(&ctl_heap[0],
 		     make_small(DOP_EXIT_TT), local, remote, token, reason);
diff --git a/erts/emulator/beam/erl_bif_trace.c b/erts/emulator/beam/erl_bif_trace.c
index 711e62c795..cf5339feb9 100644
--- a/erts/emulator/beam/erl_bif_trace.c
+++ b/erts/emulator/beam/erl_bif_trace.c
@@ -1858,6 +1858,8 @@ Eterm erts_seq_trace(Process *p, Eterm arg1, Eterm arg2,
 
     if (arg1 == am_send) {
 	current_flag = SEQ_TRACE_SEND;
+    } else if (arg1 == am_spawn) {
+	current_flag = SEQ_TRACE_SPAWN;
     } else if (arg1 == am_receive) {
 	current_flag = SEQ_TRACE_RECEIVE; 
     } else if (arg1 == am_print) {
@@ -1966,8 +1968,9 @@ BIF_RETTYPE erl_seq_trace_info(Process *p, Eterm item)
     }
 
     if (have_no_seqtrace(SEQ_TRACE_TOKEN(p))) {
-	if ((item == am_send)  || (item == am_receive) || 
-	    (item == am_print) || (item == am_timestamp)
+	if ((item == am_send) || (item == am_spawn) ||
+        (item == am_receive) || (item == am_print)
+        || (item == am_timestamp)
 	    || (item == am_monotonic_timestamp)
 	    || (item == am_strict_monotonic_timestamp)) {
 	    hp = HAlloc(p,3);
@@ -1982,6 +1985,8 @@ BIF_RETTYPE erl_seq_trace_info(Process *p, Eterm item)
 
     if (item == am_send) {
 	current_flag = SEQ_TRACE_SEND;
+    } else if (item == am_spawn) {
+	current_flag = SEQ_TRACE_SPAWN;
     } else if (item == am_receive) {
 	current_flag = SEQ_TRACE_RECEIVE; 
     } else if (item == am_print) {
@@ -2031,7 +2036,7 @@ BIF_RETTYPE seq_trace_print_1(BIF_ALIST_1)
     if (have_no_seqtrace(SEQ_TRACE_TOKEN(BIF_P))) {
 	BIF_RET(am_false);
     }
-    seq_trace_update_send(BIF_P);
+    seq_trace_update_serial(BIF_P);
     seq_trace_output(SEQ_TRACE_TOKEN(BIF_P), BIF_ARG_1, 
 		     SEQ_TRACE_PRINT, NIL, BIF_P);
     BIF_RET(am_true);
@@ -2055,7 +2060,7 @@ BIF_RETTYPE seq_trace_print_2(BIF_ALIST_2)
     }
     if (!EQ(BIF_ARG_1, SEQ_TRACE_TOKEN_LABEL(BIF_P)))
 	BIF_RET(am_false);
-    seq_trace_update_send(BIF_P);
+    seq_trace_update_serial(BIF_P);
     seq_trace_output(SEQ_TRACE_TOKEN(BIF_P), BIF_ARG_2, 
 		     SEQ_TRACE_PRINT, NIL, BIF_P);
     BIF_RET(am_true);
diff --git a/erts/emulator/beam/erl_message.c b/erts/emulator/beam/erl_message.c
index e350a20339..f69f81e2f3 100644
--- a/erts/emulator/beam/erl_message.c
+++ b/erts/emulator/beam/erl_message.c
@@ -674,7 +674,7 @@ erts_send_message(Process* sender,
          * Make sure we don't use the heap between those instances.
          */
         if (have_seqtrace(stoken)) {
-	    seq_trace_update_send(sender);
+	    seq_trace_update_serial(sender);
 	    seq_trace_output(stoken, message, SEQ_TRACE_SEND,
 			     receiver->common.id, sender);
 
diff --git a/erts/emulator/beam/erl_nif.c b/erts/emulator/beam/erl_nif.c
index af1acbfc90..4b4573d2f9 100644
--- a/erts/emulator/beam/erl_nif.c
+++ b/erts/emulator/beam/erl_nif.c
@@ -815,7 +815,7 @@ int enif_send(ErlNifEnv* env, const ErlNifPid* to_pid,
             }
 #endif
             if (have_seqtrace(stoken)) {
-                seq_trace_update_send(c_p);
+                seq_trace_update_serial(c_p);
                 seq_trace_output(stoken, msg, SEQ_TRACE_SEND,
                                  rp->common.id, c_p);
             }
diff --git a/erts/emulator/beam/erl_proc_sig_queue.c b/erts/emulator/beam/erl_proc_sig_queue.c
index 9c74a2c355..877a139d85 100644
--- a/erts/emulator/beam/erl_proc_sig_queue.c
+++ b/erts/emulator/beam/erl_proc_sig_queue.c
@@ -994,7 +994,7 @@ send_gen_exit_signal(Process *c_p, Eterm from_tag,
 
     seq_trace = c_p && have_seqtrace(token);
     if (seq_trace)
-        seq_trace_update_send(c_p);
+        seq_trace_update_serial(c_p);
 
 #ifdef USE_VM_PROBES
     utag_sz = 0;
diff --git a/erts/emulator/beam/erl_process.c b/erts/emulator/beam/erl_process.c
index 0a099e69bb..c19b270725 100644
--- a/erts/emulator/beam/erl_process.c
+++ b/erts/emulator/beam/erl_process.c
@@ -11597,9 +11597,6 @@ erl_create_process(Process* parent, /* Parent of process (default group leader).
     p->mbuf_sz = 0;
     erts_atomic_init_nob(&p->psd, (erts_aint_t) NULL);
     p->dictionary = NULL;
-    p->seq_trace_lastcnt = 0;
-    p->seq_trace_clock = 0;
-    SEQ_TRACE_TOKEN(p) = NIL;
 #ifdef USE_VM_PROBES
     DT_UTAG(p) = NIL;
     DT_UTAG_FLAGS(p) = 0;
@@ -11663,6 +11660,45 @@ erl_create_process(Process* parent, /* Parent of process (default group leader).
             trace_proc(p, locks, p, am_getting_linked, parent->common.id);
     }
 
+    if (have_seqtrace(SEQ_TRACE_TOKEN(parent))) {
+        Eterm token;
+        Uint token_sz;
+        Eterm *hp;
+
+        ASSERT(SEQ_TRACE_TOKEN_ARITY(parent) == 5);
+        ASSERT(is_immed(SEQ_TRACE_TOKEN_FLAGS(parent)));
+        ASSERT(is_immed(SEQ_TRACE_TOKEN_SERIAL(parent)));
+        ASSERT(is_immed(SEQ_TRACE_TOKEN_LASTCNT(parent)));
+
+        seq_trace_update_serial(parent);
+
+        token = SEQ_TRACE_TOKEN(parent);
+        token_sz = size_object(token);
+
+        hp = HAlloc(p, token_sz);
+        SEQ_TRACE_TOKEN(p) = copy_struct(token, token_sz, &hp, &MSO(p));
+
+        /* The counters behave the same way on spawning as they do on messages;
+         * we don't inherit our parent's lastcnt. */
+        p->seq_trace_lastcnt = parent->seq_trace_clock;
+        p->seq_trace_clock = parent->seq_trace_clock;
+
+        if ((locks & (ERTS_PROC_LOCK_STATUS|ERTS_PROC_LOCK_TRACE))
+              == (ERTS_PROC_LOCK_STATUS|ERTS_PROC_LOCK_TRACE)) {
+            /* The locks may already be released if ordinary tracing is
+             * enabled. */
+            locks &= ~(ERTS_PROC_LOCK_STATUS|ERTS_PROC_LOCK_TRACE);
+            erts_proc_unlock(p, ERTS_PROC_LOCK_STATUS|ERTS_PROC_LOCK_TRACE);
+            erts_proc_unlock(parent, ERTS_PROC_LOCK_STATUS|ERTS_PROC_LOCK_TRACE);
+        }
+
+        seq_trace_output(token, NIL, SEQ_TRACE_SPAWN, p->common.id, parent);
+    } else {
+        SEQ_TRACE_TOKEN(p) = NIL;
+        p->seq_trace_lastcnt = 0;
+        p->seq_trace_clock = 0;
+    }
+
     /*
      * Check if this process should be initially linked to its parent.
      */
diff --git a/erts/emulator/beam/erl_process.h b/erts/emulator/beam/erl_process.h
index 3b593bce02..d52b072183 100644
--- a/erts/emulator/beam/erl_process.h
+++ b/erts/emulator/beam/erl_process.h
@@ -1483,6 +1483,8 @@ extern int erts_system_profile_ts_type;
 #define SEQ_TRACE_SEND     (1 << 0)
 #define SEQ_TRACE_RECEIVE  (1 << 1)
 #define SEQ_TRACE_PRINT    (1 << 2)
+/* (This three-bit gap contains the timestamp.) */
+#define SEQ_TRACE_SPAWN    (1 << 6)
 
 #define ERTS_SEQ_TRACE_FLAGS_TS_TYPE_SHIFT 3
 
diff --git a/erts/emulator/beam/erl_trace.c b/erts/emulator/beam/erl_trace.c
index ae7084b7f4..e3b775b451 100644
--- a/erts/emulator/beam/erl_trace.c
+++ b/erts/emulator/beam/erl_trace.c
@@ -824,7 +824,7 @@ trace_receive(Process* receiver,
 }
 
 int
-seq_trace_update_send(Process *p)
+seq_trace_update_serial(Process *p)
 {
     ErtsTracer seq_tracer = erts_get_system_seq_tracer();
     ASSERT((is_tuple(SEQ_TRACE_TOKEN(p)) || is_nil(SEQ_TRACE_TOKEN(p))));
@@ -892,6 +892,7 @@ seq_trace_output_generic(Eterm token, Eterm msg, Uint type,
 
     switch (type) {
     case SEQ_TRACE_SEND:    type_atom = am_send; break;
+    case SEQ_TRACE_SPAWN:   type_atom = am_spawn; break;
     case SEQ_TRACE_PRINT:   type_atom = am_print; break;
     case SEQ_TRACE_RECEIVE: type_atom = am_receive; break;
     default:
diff --git a/erts/emulator/beam/erl_trace.h b/erts/emulator/beam/erl_trace.h
index b7844d1cb0..bb5c9ac276 100644
--- a/erts/emulator/beam/erl_trace.h
+++ b/erts/emulator/beam/erl_trace.h
@@ -163,7 +163,9 @@ seq_trace_output_generic((token), (msg), (type), (receiver), NULL, (exitfrom))
 void seq_trace_output_generic(Eterm token, Eterm msg, Uint type, 
 			      Eterm receiver, Process *process, Eterm exitfrom);
 
-int seq_trace_update_send(Process *process);
+/* Bump the sequence number if tracing is enabled; must be used before sending
+ * send/spawn trace messages. */
+int seq_trace_update_serial(Process *process);
 
 Eterm erts_seq_trace(Process *process, 
 		     Eterm atom_type, Eterm atom_true_or_false, 
diff --git a/lib/kernel/doc/src/seq_trace.xml b/lib/kernel/doc/src/seq_trace.xml
index 9aef748594..aa9067f082 100644
--- a/lib/kernel/doc/src/seq_trace.xml
+++ b/lib/kernel/doc/src/seq_trace.xml
@@ -107,6 +107,12 @@ seq_trace:set_token(OldToken), % activate the trace token again
               enables/disables tracing on message sending. Default is
               <c>false</c>.</p>
           </item>
+          <tag><c>set_token('spawn', <anno>Bool</anno>)</c></tag>
+          <item>
+            <p>A trace token flag (<c>true | false</c>) which
+              enables/disables tracing on process spawning. Default is
+              <c>false</c>.</p>
+          </item>
           <tag><c>set_token('receive', <anno>Bool</anno>)</c></tag>
           <item>
             <p>A trace token flag (<c>true | false</c>) which
@@ -259,6 +265,11 @@ TimeStamp = {Seconds, Milliseconds, Microseconds}
         <p>Used when a process <c>From</c> with its trace token flag
           <c>send</c> set to <c>true</c> has sent a message.</p>
       </item>
+      <tag><c>{spawn, Serial, Parent, Child, _}</c></tag>
+      <item>
+        <p>Used when a process <c>Parent</c> with its trace token flag
+          <c>spawn</c> set to <c>true</c> has spawned a process.</p>
+      </item>
       <tag><c>{'receive', Serial, From, To, Message}</c></tag>
       <item>
         <p>Used when a process <c>To</c> receives a message with a
@@ -295,8 +306,8 @@ TimeStamp = {Seconds, Milliseconds, Microseconds}
       is initiated by a single message. In short, it works as follows:</p>
     <p>Each process has a <em>trace token</em>, which can be empty or
       not empty. When not empty, the trace token can be seen as
-      the tuple <c>{Label, Flags, Serial, From}</c>. The trace token is
-      passed invisibly with each message.</p>
+      the tuple <c>{Label, Flags, Serial, From}</c>. The trace token is passed
+      invisibly to spawned processes and with each message sent.</p>
     <p>To start a sequential trace, the user must explicitly set
       the trace token in the process that will send the first message
       in a sequence.</p>
@@ -306,9 +317,10 @@ TimeStamp = {Seconds, Milliseconds, Microseconds}
     <p>On each Erlang node, a process can be set as the <em>system tracer</em>.
       This process will receive trace messages each time
       a message with a trace token is sent or received (if the trace
-      token flag <c>send</c> or <c>'receive'</c> is set). The system
-      tracer can then print each trace event, write it to a file, or
-      whatever suitable.</p>
+      token flag <c>send</c> or <c>'receive'</c> is set), and when a process
+      with a non-empty trace token spawns another (if the trace token flag
+      <c>spawn</c> is set). The system tracer can then print each trace event,
+      write it to a file, or whatever suitable.</p>
     <note>
       <p>The system tracer only receives those trace events that
         occur locally within the Erlang node. To get the whole picture
@@ -322,10 +334,9 @@ TimeStamp = {Seconds, Milliseconds, Microseconds}
 
   <section>
     <title>Trace Token</title>
-    <p>Each process has a current trace token. Initially, the token is
-      empty. When the process sends a message to another process, a
-      copy of the current token is sent "invisibly" along with
-      the message.</p>
+    <p>Each process has a current trace token, which is copied from the process
+      that spawned it. When a process sends a message to another process, a
+      copy of the current token is sent "invisibly" along with the message.</p>
     <p>The current token of a process is set in one of the following two
       ways:</p>
     <list type="bulleted">
@@ -354,8 +365,9 @@ TimeStamp = {Seconds, Milliseconds, Microseconds}
     <p>The algorithm for updating <c>Serial</c> can be described as
       follows:</p>
     <p>Let each process have two counters, <c>prev_cnt</c> and
-      <c>curr_cnt</c>, both are set to <c>0</c> when a process is created.
-      The counters are updated at the following occasions:</p>
+      <c>curr_cnt</c>, both are set to <c>0</c> when a process is created
+      outside of a trace sequence. The counters are updated at the following
+      occasions:</p>
     <list type="bulleted">
       <item>
         <p><em>When the process is about to send a message and the trace token
@@ -369,6 +381,16 @@ tcurr := curr_cnt</pre>
         <p>The trace token with <c>tprev</c> and <c>tcurr</c> is then
           passed along with the message.</p>
       </item>
+      <item>
+        <p><em>When the process is about to spawn another process and the trace
+          token is not empty.</em></p>
+        <p>The counters of the parent process are updated in the same way as
+          for send above. The trace token is then passed to the child process,
+          whose counters will be set as follows:</p>
+        <code>
+curr_cnt := tcurr
+prev_cnt := tcurr</code>
+      </item>
       <item>
         <p><em>When the process calls</em> <c>seq_trace:print(Label, Info)</c>,
           <c>Label</c> <em>matches the label part of the trace token and the
@@ -487,9 +509,9 @@ tracer() ->
            print_trace(Label,TraceInfo,false);
         {seq_trace,Label,TraceInfo,Ts} ->
            print_trace(Label,TraceInfo,Ts);
-        Other -> ignore
+        _Other -> ignore
     end,
-    tracer().        
+    tracer().
 
 print_trace(Label,TraceInfo,false) ->
     io:format("~p:",[Label]),
@@ -504,8 +526,11 @@ print_trace({'receive',Serial,From,To,Message}) ->
     io:format("~p Received ~p FROM ~p WITH~n~p~n", 
               [To,Serial,From,Message]);
 print_trace({send,Serial,From,To,Message}) ->
-    io:format("~p Sent ~p TO ~p WITH~n~p~n", 
-              [From,Serial,To,Message]).</code>
+    io:format("~p Sent ~p TO ~p WITH~n~p~n",
+              [From,Serial,To,Message]);
+print_trace({spawn,Serial,Parent,Child,_}) ->
+    io:format("~p Spawned ~p AT ~p~n",
+              [Parent,Child,Serial]).</code>
     <p>The code that creates a process that runs this tracer function
       and sets that process as the system tracer can look like this:</p>
     <code type="none">
diff --git a/lib/kernel/src/seq_trace.erl b/lib/kernel/src/seq_trace.erl
index 4f9d7b3e5c..327754d9ac 100644
--- a/lib/kernel/src/seq_trace.erl
+++ b/lib/kernel/src/seq_trace.erl
@@ -20,12 +20,14 @@
 
 -module(seq_trace).
 
--define(SEQ_TRACE_SEND, 1).       %(1 << 0)
--define(SEQ_TRACE_RECEIVE, 2).    %(1 << 1)
--define(SEQ_TRACE_PRINT, 4).      %(1 << 2)
--define(SEQ_TRACE_NOW_TIMESTAMP, 8). %(1 << 3)
--define(SEQ_TRACE_STRICT_MON_TIMESTAMP, 16). %(1 << 4)
--define(SEQ_TRACE_MON_TIMESTAMP, 32). %(1 << 5)
+%% Don't forget to update seq_trace_SUITE after changing these.
+-define(SEQ_TRACE_SEND, 1).                     %(1 << 0)
+-define(SEQ_TRACE_RECEIVE, 2).                  %(1 << 1)
+-define(SEQ_TRACE_PRINT, 4).                    %(1 << 2)
+-define(SEQ_TRACE_NOW_TIMESTAMP, 8).            %(1 << 3)
+-define(SEQ_TRACE_STRICT_MON_TIMESTAMP, 16).    %(1 << 4)
+-define(SEQ_TRACE_MON_TIMESTAMP, 32).           %(1 << 5)
+-define(SEQ_TRACE_SPAWN, 64).                   %(1 << 6)
 
 -export([set_token/1,
 	 set_token/2,
@@ -39,7 +41,8 @@
 
 %%---------------------------------------------------------------------------
 
--type flag()       :: 'send' | 'receive' | 'print' | 'timestamp' | 'monotonic_timestamp' | 'strict_monotonic_timestamp'.
+-type flag()       :: 'send' | 'spawn' | 'receive' | 'print' | 'timestamp' |
+                      'monotonic_timestamp' | 'strict_monotonic_timestamp'.
 -type component()  :: 'label' | 'serial' | flag().
 -type value()      :: (Label :: term())
                     | {Previous :: non_neg_integer(),
@@ -142,10 +145,11 @@ set_token2([]) ->
 decode_flags(Flags) ->
     Print = (Flags band ?SEQ_TRACE_PRINT) > 0,
     Send = (Flags band ?SEQ_TRACE_SEND) > 0,
+    Spawn = (Flags band ?SEQ_TRACE_SPAWN) > 0,
     Rec = (Flags band ?SEQ_TRACE_RECEIVE) > 0,
     NowTs = (Flags band ?SEQ_TRACE_NOW_TIMESTAMP) > 0,
     StrictMonTs = (Flags band ?SEQ_TRACE_STRICT_MON_TIMESTAMP) > 0,
     MonTs = (Flags band ?SEQ_TRACE_MON_TIMESTAMP) > 0,
-    [{print,Print},{send,Send},{'receive',Rec},{timestamp,NowTs},
+    [{print,Print},{send,Send},{spawn,Spawn},{'receive',Rec},{timestamp,NowTs},
      {strict_monotonic_timestamp, StrictMonTs},
      {monotonic_timestamp, MonTs}].
diff --git a/lib/kernel/test/seq_trace_SUITE.erl b/lib/kernel/test/seq_trace_SUITE.erl
index 663f910751..3256b6e9ad 100644
--- a/lib/kernel/test/seq_trace_SUITE.erl
+++ b/lib/kernel/test/seq_trace_SUITE.erl
@@ -29,7 +29,7 @@
 	 send/1, distributed_send/1, recv/1, distributed_recv/1,
 	 trace_exit/1, distributed_exit/1, call/1, port/1,
 	 match_set_seq_token/1, gc_seq_token/1, label_capability_mismatch/1,
-         send_literal/1]).
+         send_literal/1,inherit_on_spawn/1,spawn_flag/1]).
 
 %% internal exports
 -export([simple_tracer/2, one_time_receiver/0, one_time_receiver/1,
@@ -51,7 +51,8 @@ all() ->
      distributed_send, recv, distributed_recv, trace_exit,
      old_heap_token, mature_heap_token,
      distributed_exit, call, port, match_set_seq_token,
-     gc_seq_token, label_capability_mismatch].
+     gc_seq_token, label_capability_mismatch,
+     inherit_on_spawn, spawn_flag].
 
 groups() -> 
     [].
@@ -81,14 +82,29 @@ token_set_get(Config) when is_list(Config) ->
     do_token_set_get(timestamp),
     do_token_set_get(monotonic_timestamp),
     do_token_set_get(strict_monotonic_timestamp).
-    
+
+-define(SEQ_TRACE_SEND, 1).                     %(1 << 0)
+-define(SEQ_TRACE_RECEIVE, 2).                  %(1 << 1)
+-define(SEQ_TRACE_PRINT, 4).                    %(1 << 2)
+-define(SEQ_TRACE_NOW_TIMESTAMP, 8).            %(1 << 3)
+-define(SEQ_TRACE_STRICT_MON_TIMESTAMP, 16).    %(1 << 4)
+-define(SEQ_TRACE_MON_TIMESTAMP, 32).           %(1 << 5)
+-define(SEQ_TRACE_SPAWN, 64).                   %(1 << 6)
+
 do_token_set_get(TsType) ->
-    io:format("Testing ~p~n", [TsType]),
+    BaseOpts = ?SEQ_TRACE_SEND bor
+               ?SEQ_TRACE_RECEIVE bor
+               ?SEQ_TRACE_PRINT bor
+               ?SEQ_TRACE_SPAWN,
     Flags = case TsType of
-		timestamp -> 15;
-		strict_monotonic_timestamp -> 23;
-		monotonic_timestamp -> 39
-	    end,
+        timestamp ->
+            BaseOpts bor ?SEQ_TRACE_NOW_TIMESTAMP;
+        strict_monotonic_timestamp ->
+            BaseOpts bor ?SEQ_TRACE_STRICT_MON_TIMESTAMP;
+        monotonic_timestamp ->
+            BaseOpts bor ?SEQ_TRACE_MON_TIMESTAMP
+        end,
+    ct:pal("Type ~p, flags = ~p~n", [TsType, Flags]),
     Self = self(),
     seq_trace:reset_trace(),
     %% Test that initial seq_trace is disabled
@@ -100,6 +116,8 @@ do_token_set_get(TsType) ->
     {print,true} = seq_trace:get_token(print),
     false = seq_trace:set_token(send,true),
     {send,true} = seq_trace:get_token(send),
+    false = seq_trace:set_token(spawn,true),
+    {spawn,true} = seq_trace:get_token(spawn),
     false = seq_trace:set_token('receive',true),
     {'receive',true} = seq_trace:get_token('receive'),
     false = seq_trace:set_token(TsType,true),
@@ -462,8 +480,6 @@ call(Config) when is_list(Config) ->
     1 =
 	erlang:trace(Self, true, 
 		     [call, set_on_spawn, {tracer, TrB(pid)}]),
-    Label = 17,
-    seq_trace:set_token(label, Label), % Token enters here!!
     RefB = make_ref(),
     Pid2B = spawn_link(
 		    fun() ->
@@ -477,6 +493,12 @@ call(Config) when is_list(Config) ->
 			    RefB = call_tracee_1(RefB),
 			    Pid2B ! {self(), msg, RefB}
 		    end),
+
+    %% The token is set *AFTER* spawning to make sure we're testing that the
+    %% token follows on send and not that it inherits on spawn.
+    Label = 17,
+    seq_trace:set_token(label, Label),
+
     Pid1B ! {Self, msg, RefB},
     %% The message is passed Self -> Pid1B -> Pid2B -> Self, and the 
     %% seq_trace token follows invisibly. Traced functions are 
@@ -497,6 +519,62 @@ call(Config) when is_list(Config) ->
     seq_trace:reset_trace(),
     ok.
 
+%% The token should follow spawn, just like it follows messages.
+inherit_on_spawn(Config) when is_list(Config) ->
+    seq_trace:reset_trace(),
+    start_tracer(),
+
+    Ref = make_ref(),
+    seq_trace:set_token(label,Ref),
+    set_token_flags([send]),
+
+    Self = self(),
+    Other = spawn(fun() -> Self ! {gurka,Ref} end),
+
+    receive {gurka,Ref} -> ok end,
+    seq_trace:reset_trace(),
+
+    [{Ref,{send,_,Other,Self,{gurka,Ref}}, _Ts}] = stop_tracer(1),
+
+    ok.
+
+spawn_flag(Config) when is_list(Config) ->
+    seq_trace:reset_trace(),
+    start_tracer(),
+
+    Ref = make_ref(),
+    seq_trace:set_token(label,Ref),
+    set_token_flags([spawn]),
+
+    Self = self(),
+
+    {serial,{0,0}} = seq_trace:get_token(serial),
+
+    %% The serial number is bumped on spawning (just like message passing), so
+    %% our child should inherit a counter of 1.
+    ProcessA = spawn(fun() ->
+                             {serial,{0,1}} = seq_trace:get_token(serial),
+                             Self ! {a,Ref}
+                     end),
+    receive {a,Ref} -> ok end,
+
+    {serial,{1,2}} = seq_trace:get_token(serial),
+
+    ProcessB = spawn(fun() ->
+                             {serial,{2,3}} = seq_trace:get_token(serial),
+                             Self ! {b,Ref} 
+                     end),
+    receive {b,Ref} -> ok end,
+
+    {serial,{3,4}} = seq_trace:get_token(serial),
+
+    seq_trace:reset_trace(),
+
+    [{Ref,{spawn,{0,1},Self,ProcessA,[]}, _Ts},
+     {Ref,{spawn,{2,3},Self,ProcessB,[]}, _Ts}] = stop_tracer(2),
+
+    ok.
+
 %% Send trace messages to a port.
 port(Config) when is_list(Config) ->
     lists:foreach(fun (TsType) -> do_port(TsType, Config) end,
diff --git a/lib/observer/test/ttb_SUITE.erl b/lib/observer/test/ttb_SUITE.erl
index 33133dd78d..f8bb2e5eb0 100644
--- a/lib/observer/test/ttb_SUITE.erl
+++ b/lib/observer/test/ttb_SUITE.erl
@@ -658,11 +658,13 @@ seq_trace(Config) when is_list(Config) ->
     ?line ok = ttb:format(
 		 [filename:join(Privdir,atom_to_list(Node)++"-seq_trace")]),
     ?line [{trace_ts,StartProc,call,{?MODULE,seq,[]},{_,_,_}},
-	   {seq_trace,0,{send,{0,1},StartProc,P1Proc,{Start,P2}}},
-	   {seq_trace,0,{send,{1,2},P1Proc,P2Proc,{P1,Start}}},
-	   {seq_trace,0,{send,{2,3},P2Proc,StartProc,{P2,P1}}},
+	   {seq_trace,0,{send,{First, Seq0},StartProc,P1Proc,{Start,P2}}},
+	   {seq_trace,0,{send,{Seq0,  Seq1},P1Proc,P2Proc,{P1,Start}}},
+	   {seq_trace,0,{send,{Seq1,  Last},P2Proc,StartProc,{P2,P1}}},
 	   end_of_trace] = flush(),
-
+    true = First < Seq0,
+    true = Seq0 < Seq1,
+    true = Seq1 < Last,
    %% Additional test for metatrace
     case StartProc of
 	{Start,_,_} -> ok;
-- 
2.16.4

openSUSE Build Service is sponsored by