[m-rev.] diff 2/2: Rename ThreadScope symbols and comments

Paul Bone paul at bone.id.au
Fri May 30 16:48:48 AEST 2014


Branches: master

Note that I will rename the "threadscope" grade and update
README.ThreadScope in a seperate change.

---

Rename ThreadScope symbols and comments

To reflect our lack of compatibility with ThreadScope this patch renames
many of the symbols used in the runtime system and compiler.

Generally "ThreadScope" is being renamed to "Parallel Profiling" and the new
tool (NIY) should be called "the Mercury Parallelism Profiler".

    + Rename the MR_THREADSCOPE macro to MR_PARPROF.  This macro is
      controlled by the threadscope grade component.
    + Rename symbols and comments in the runtime that used the term
      "threadscope" or "ts".

There are no algorithmic changes in this patch.

compiler/code_info.m:
compiler/compile_target_code.m:
compiler/dep_par_conj.m:
compiler/global_data.m:
compiler/hlds_module.m:
compiler/layout.m:
compiler/layout_out.m:
compiler/llds.m:
compiler/llds_out_file.m:
compiler/mercury_compile_llds_back_end.m:
compiler/opt_debug.m:
compiler/par_conj_gen.m:
compiler/proc_gen.m:
library/benchmarking.m:
library/par_builtin.m:
runtime/mercury_atomic_ops.h:
runtime/mercury_conf_param.h:
runtime/mercury_context.c:
runtime/mercury_context.h:
runtime/mercury_debug.c:
runtime/mercury_debug.h:
runtime/mercury_engine.c:
runtime/mercury_engine.h:
runtime/mercury_grade.h:
runtime/mercury_memory_handlers.c:
runtime/mercury_misc.h:
runtime/mercury_par_builtin.h:
runtime/mercury_par_profile.c:
runtime/mercury_par_profile.h:
runtime/mercury_thread.c:
runtime/mercury_wrapper.c:
runtime/mercury_wrapper.h:
scripts/mgnuc.in:
util/mkinit.c:
    As above.
---
 compiler/code_info.m                     |  26 +-
 compiler/compile_target_code.m           |   2 +-
 compiler/dep_par_conj.m                  | 117 +++----
 compiler/global_data.m                   |  44 +--
 compiler/hlds_module.m                   |  32 +-
 compiler/layout.m                        |   2 +-
 compiler/layout_out.m                    |  35 +-
 compiler/llds.m                          |   2 +-
 compiler/llds_out_file.m                 |  22 +-
 compiler/mercury_compile_llds_back_end.m |  10 +-
 compiler/opt_debug.m                     |   4 +-
 compiler/par_conj_gen.m                  |   8 +-
 compiler/proc_gen.m                      |  10 +-
 library/benchmarking.m                   |   2 +-
 library/par_builtin.m                    |   2 +-
 runtime/mercury_atomic_ops.h             |   2 +-
 runtime/mercury_conf_param.h             |  18 +-
 runtime/mercury_context.c                |  94 ++---
 runtime/mercury_context.h                |  22 +-
 runtime/mercury_debug.c                  |   6 +-
 runtime/mercury_debug.h                  |   4 +-
 runtime/mercury_engine.c                 |   8 +-
 runtime/mercury_engine.h                 |   8 +-
 runtime/mercury_grade.h                  |   2 +-
 runtime/mercury_memory_handlers.c        |   6 +-
 runtime/mercury_misc.h                   |   4 +-
 runtime/mercury_par_builtin.h            |  24 +-
 runtime/mercury_par_profile.c            | 565 ++++++++++++++++---------------
 runtime/mercury_par_profile.h            | 108 +++---
 runtime/mercury_thread.c                 |  12 +-
 runtime/mercury_wrapper.c                |  44 +--
 runtime/mercury_wrapper.h                |   5 +-
 scripts/mgnuc.in                         |   2 +-
 util/mkinit.c                            |  24 +-
 34 files changed, 642 insertions(+), 634 deletions(-)

diff --git a/compiler/code_info.m b/compiler/code_info.m
index 19b5398..e680be8 100644
--- a/compiler/code_info.m
+++ b/compiler/code_info.m
@@ -493,12 +493,12 @@
                 cip_used_env_vars           :: set(string),
 
                 % A counter and table for allocating and maintaining slots
-                % where string IDs will be placed at runtime for threadscope
+                % where string IDs will be placed at runtime for parallel
                 % profiling.  The actual string IDs are allocated at runtime
                 % and their IDs are placed in an array slot which can be
                 % referred to statically.
-                cip_ts_string_table_size    :: int,
-                cip_ts_rev_string_table     :: list(string),
+                cip_pp_string_table_size    :: int,
+                cip_pp_rev_string_table     :: list(string),
 
                 % Code that is part of this procedure, but that can be placed
                 % after the procedure without a cache penalty.  For example,
@@ -979,10 +979,10 @@ get_out_of_line_code(CI, CI ^ code_info_persistent ^ cip_out_of_line_code).
 :- pred add_closure_layout(closure_proc_id_data::in,
     code_info::in, code_info::out) is det.
 
-:- pred add_threadscope_string(string::in, int::out,
+:- pred add_parprof_string(string::in, int::out,
     code_info::in, code_info::out) is det.
 
-:- pred get_threadscope_rev_string_table(code_info::in,
+:- pred get_parprof_rev_string_table(code_info::in,
     list(string)::out, int::out) is det.
 
 :- pred add_scalar_static_cell(list(typed_rval)::in,
@@ -1254,18 +1254,18 @@ add_closure_layout(ClosureLayout, !CI) :-
     get_closure_layouts(!.CI, ClosureLayouts),
     set_closure_layouts([ClosureLayout | ClosureLayouts], !CI).
 
-add_threadscope_string(String, SlotNum, !CI) :-
-    Size0 = !.CI ^ code_info_persistent ^ cip_ts_string_table_size,
-    RevTable0 = !.CI ^ code_info_persistent ^ cip_ts_rev_string_table,
+add_parprof_string(String, SlotNum, !CI) :-
+    Size0 = !.CI ^ code_info_persistent ^ cip_pp_string_table_size,
+    RevTable0 = !.CI ^ code_info_persistent ^ cip_pp_rev_string_table,
     SlotNum = Size0,
     Size = Size0 + 1,
     RevTable = [String | RevTable0],
-    !CI ^ code_info_persistent ^ cip_ts_string_table_size := Size,
-    !CI ^ code_info_persistent ^ cip_ts_rev_string_table := RevTable.
+    !CI ^ code_info_persistent ^ cip_pp_string_table_size := Size,
+    !CI ^ code_info_persistent ^ cip_pp_rev_string_table := RevTable.
 
-get_threadscope_rev_string_table(CI, RevTable, TableSize) :-
-    RevTable = CI ^ code_info_persistent ^ cip_ts_rev_string_table,
-    TableSize = CI ^ code_info_persistent ^ cip_ts_string_table_size.
+get_parprof_rev_string_table(CI, RevTable, TableSize) :-
+    RevTable = CI ^ code_info_persistent ^ cip_pp_rev_string_table,
+    TableSize = CI ^ code_info_persistent ^ cip_pp_string_table_size.
 
 add_scalar_static_cell(RvalsTypes, DataAddr, !CI) :-
     get_static_cell_info(!.CI, StaticCellInfo0),
diff --git a/compiler/compile_target_code.m b/compiler/compile_target_code.m
index db24324..a7b5f0f 100644
--- a/compiler/compile_target_code.m
+++ b/compiler/compile_target_code.m
@@ -699,7 +699,7 @@ gather_grade_defines(Globals, PIC, GradeDefines) :-
     globals.lookup_bool_option(Globals, threadscope, Threadscope),
     (
         Threadscope = yes,
-        ThreadscopeOpt = "-DMR_THREADSCOPE "
+        ThreadscopeOpt = "-DMR_PARPROF "
     ;
         Threadscope = no,
         ThreadscopeOpt = ""
diff --git a/compiler/dep_par_conj.m b/compiler/dep_par_conj.m
index 42ad26e..a0df8a6 100644
--- a/compiler/dep_par_conj.m
+++ b/compiler/dep_par_conj.m
@@ -180,10 +180,10 @@ impl_dep_par_conjs_in_module(!ModuleInfo) :-
     % Phase one: insert synchronization code into all parallel conjunctions
     % in the module.
     module_info_get_valid_predids(PredIds, !ModuleInfo),
-    module_info_get_ts_rev_string_table(!.ModuleInfo, _, RevTable0),
-    make_ts_string_table(RevTable0, TSStringTable0),
+    module_info_get_parprof_rev_string_table(!.ModuleInfo, _, RevTable0),
+    make_pp_string_table(RevTable0, PPStringTable0),
     list.foldl3(maybe_sync_dep_par_conjs_in_pred, PredIds,
-        !ModuleInfo, [], ProcsToScan, TSStringTable0, TSStringTable1),
+        !ModuleInfo, [], ProcsToScan, PPStringTable0, PPStringTable1),
 
     % Phase two: attempt to push the synchronization code inside procedures
     % as far as we can. We do this by creating specialized versions of
@@ -201,9 +201,9 @@ impl_dep_par_conjs_in_module(!ModuleInfo) :-
         Pushability0, Pushability, RevProcMap0, RevProcMap),
     add_requested_specialized_par_procs(PendingParProcs, Pushability,
         DoneParProcs0, InitialModuleInfo, !ModuleInfo, RevProcMap, _,
-        TSStringTable1, TSStringTable),
-    module_info_set_ts_rev_string_table(TSStringTable ^ st_size,
-        TSStringTable ^ st_rev_table, !ModuleInfo).
+        PPStringTable1, PPStringTable),
+    module_info_set_parprof_rev_string_table(PPStringTable ^ pp_size,
+        PPStringTable ^ pp_rev_table, !ModuleInfo).
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
@@ -237,29 +237,29 @@ impl_dep_par_conjs_in_module(!ModuleInfo) :-
                 % The current procedure.
                 sync_this_proc              :: pred_proc_id,
 
-                % The current threadscope string table.
-                sync_ts_string_table        :: ts_string_table
+                % The current parallel profiling string table.
+                sync_pp_string_table        :: pp_string_table
             ).
 
 :- pred maybe_sync_dep_par_conjs_in_pred(pred_id::in,
     module_info::in, module_info::out,
     list(pred_proc_id)::in, list(pred_proc_id)::out,
-    ts_string_table::in, ts_string_table::out) is det.
+    pp_string_table::in, pp_string_table::out) is det.
 
 maybe_sync_dep_par_conjs_in_pred(PredId, !ModuleInfo, !ProcsToScan,
-        !TSStringTable) :-
+        !PPStringTable) :-
     module_info_pred_info(!.ModuleInfo, PredId, PredInfo),
     ProcIds = pred_info_non_imported_procids(PredInfo),
     list.foldl3(maybe_sync_dep_par_conjs_in_proc(PredId), ProcIds,
-        !ModuleInfo, !ProcsToScan, !TSStringTable).
+        !ModuleInfo, !ProcsToScan, !PPStringTable).
 
 :- pred maybe_sync_dep_par_conjs_in_proc(pred_id::in, proc_id::in,
     module_info::in, module_info::out,
     list(pred_proc_id)::in, list(pred_proc_id)::out,
-    ts_string_table::in, ts_string_table::out) is det.
+    pp_string_table::in, pp_string_table::out) is det.
 
 maybe_sync_dep_par_conjs_in_proc(PredId, ProcId, !ModuleInfo, !ProcsToScan,
-        !TSStringTable) :-
+        !PPStringTable) :-
     module_info_proc_info(!.ModuleInfo, PredId, ProcId, ProcInfo),
     proc_info_get_has_parallel_conj(ProcInfo, HasParallelConj),
     (
@@ -267,16 +267,16 @@ maybe_sync_dep_par_conjs_in_proc(PredId, ProcId, !ModuleInfo, !ProcsToScan,
     ;
         HasParallelConj = yes,
         sync_dep_par_conjs_in_proc(PredId, ProcId, set_of_var.init,
-            !ModuleInfo, !ProcsToScan, !TSStringTable)
+            !ModuleInfo, !ProcsToScan, !PPStringTable)
     ).
 
 :- pred sync_dep_par_conjs_in_proc(pred_id::in, proc_id::in,
     set_of_progvar::in, module_info::in, module_info::out,
     list(pred_proc_id)::in, list(pred_proc_id)::out,
-    ts_string_table::in, ts_string_table::out) is det.
+    pp_string_table::in, pp_string_table::out) is det.
 
 sync_dep_par_conjs_in_proc(PredId, ProcId, IgnoreVars, !ModuleInfo,
-        !ProcsToScan, !TSStringTable) :-
+        !ProcsToScan, !PPStringTable) :-
     some [!PredInfo, !ProcInfo, !Goal, !VarSet, !VarTypes, !SyncInfo] (
         module_info_pred_proc_info(!.ModuleInfo, PredId, ProcId,
             !:PredInfo, !:ProcInfo),
@@ -295,10 +295,10 @@ sync_dep_par_conjs_in_proc(PredId, ProcId, IgnoreVars, !ModuleInfo,
 
         GoalBeforeDepParConj = !.Goal,
         !:SyncInfo = sync_info(!.ModuleInfo, IgnoreVars, AllowSomePathsOnly,
-            !.VarSet, !.VarTypes, proc(PredId, ProcId), !.TSStringTable),
+            !.VarSet, !.VarTypes, proc(PredId, ProcId), !.PPStringTable),
         sync_dep_par_conjs_in_goal(!Goal, InstMap0, _, !SyncInfo),
         !.SyncInfo = sync_info(_, _, _, !:VarSet, !:VarTypes, _,
-            !:TSStringTable),
+            !:PPStringTable),
         % XXX RTTI varmaps may need to be updated
 
         trace [compile_time(flag("debug-dep-par-conj")), io(!IO)] (
@@ -467,7 +467,7 @@ sync_dep_par_conjs_in_cases([Case0 | Cases0], [Case | Cases], InstMap0,
 
 maybe_sync_dep_par_conj(Conjuncts, GoalInfo, NewGoal, InstMap, !SyncInfo) :-
     !.SyncInfo = sync_info(ModuleInfo0, IgnoreVars, AllowSomePathsOnly,
-        VarSet0, VarTypes0, PredProcId, TSStringTable0),
+        VarSet0, VarTypes0, PredProcId, PPStringTable0),
     % Find the variables that are shared between conjuncts.
     SharedVars0 = find_shared_variables(ModuleInfo0, InstMap, Conjuncts),
 
@@ -487,7 +487,7 @@ maybe_sync_dep_par_conj(Conjuncts, GoalInfo, NewGoal, InstMap, !SyncInfo) :-
             reorder_indep_par_conj(PredProcId, VarTypes0, InstMap, Conjuncts,
                 GoalInfo, NewGoal, ModuleInfo0, ModuleInfo),
             !:SyncInfo = sync_info(ModuleInfo, IgnoreVars, AllowSomePathsOnly,
-                VarSet0, VarTypes0, PredProcId, TSStringTable0)
+                VarSet0, VarTypes0, PredProcId, PPStringTable0)
         ;
             ParLoopControl = yes,
             % Don't swap the conjuncts, parallel loop control can do a better
@@ -497,10 +497,10 @@ maybe_sync_dep_par_conj(Conjuncts, GoalInfo, NewGoal, InstMap, !SyncInfo) :-
     ;
         sync_dep_par_conj(ModuleInfo0, AllowSomePathsOnly, SharedVars,
             Conjuncts, GoalInfo, NewGoal, InstMap,
-            VarSet0, VarSet, VarTypes0, VarTypes, TSStringTable0,
-            TSStringTable),
+            VarSet0, VarSet, VarTypes0, VarTypes, PPStringTable0,
+            PPStringTable),
         !:SyncInfo = sync_info(ModuleInfo0, IgnoreVars, AllowSomePathsOnly,
-            VarSet, VarTypes, PredProcId, TSStringTable)
+            VarSet, VarTypes, PredProcId, PPStringTable)
     ).
 
     % Transforming the parallel conjunction.
@@ -530,14 +530,14 @@ maybe_sync_dep_par_conj(Conjuncts, GoalInfo, NewGoal, InstMap, !SyncInfo) :-
 :- pred sync_dep_par_conj(module_info::in, bool::in, set_of_progvar::in,
     list(hlds_goal)::in, hlds_goal_info::in, hlds_goal::out, instmap::in,
     prog_varset::in, prog_varset::out, vartypes::in, vartypes::out,
-    ts_string_table::in, ts_string_table::out) is det.
+    pp_string_table::in, pp_string_table::out) is det.
 
 sync_dep_par_conj(ModuleInfo, AllowSomePathsOnly, SharedVars, Goals, GoalInfo,
-        NewGoal, InstMap, !VarSet, !VarTypes, !TSStringTable) :-
+        NewGoal, InstMap, !VarSet, !VarTypes, !PPStringTable) :-
     SharedVarsList = set_of_var.to_sorted_list(SharedVars),
     list.map_foldl4(allocate_future(ModuleInfo), SharedVarsList,
         AllocateFuturesGoals, !VarSet, !VarTypes, map.init, FutureMap,
-        !TSStringTable),
+        !PPStringTable),
     list.condense(AllocateFuturesGoals, AllocateFutures),
     list.map_foldl3(
         sync_dep_par_conjunct(ModuleInfo, AllowSomePathsOnly, SharedVars,
@@ -1603,11 +1603,11 @@ find_specialization_requests_in_proc(DoneProcs, InitialModuleInfo, PredProcId,
 :- pred add_requested_specialized_par_procs(pending_par_procs::in,
     pushable_args_map::in, done_par_procs::in, module_info::in,
     module_info::in, module_info::out, rev_proc_map::in, rev_proc_map::out,
-    ts_string_table::in, ts_string_table::out) is det.
+    pp_string_table::in, pp_string_table::out) is det.
 
 add_requested_specialized_par_procs(!.PendingParProcs, !.Pushability,
         !.DoneParProcs, InitialModuleInfo, !ModuleInfo, !RevProcMap,
-        !TSStringTable) :-
+        !PPStringTable) :-
     (
         !.PendingParProcs = []
     ;
@@ -1617,10 +1617,10 @@ add_requested_specialized_par_procs(!.PendingParProcs, !.Pushability,
         map.det_insert(CallPattern, NewProc, !DoneParProcs),
         add_requested_specialized_par_proc(CallPattern, NewProc,
             !PendingParProcs, !Pushability, !.DoneParProcs, InitialModuleInfo,
-            !ModuleInfo, !RevProcMap, !TSStringTable),
+            !ModuleInfo, !RevProcMap, !PPStringTable),
         add_requested_specialized_par_procs(!.PendingParProcs, !.Pushability,
             !.DoneParProcs, InitialModuleInfo, !ModuleInfo, !RevProcMap,
-            !TSStringTable)
+            !PPStringTable)
     ).
 
 :- pred add_requested_specialized_par_proc(par_proc_call_pattern::in,
@@ -1628,11 +1628,11 @@ add_requested_specialized_par_procs(!.PendingParProcs, !.Pushability,
     pushable_args_map::in, pushable_args_map::out, done_par_procs::in,
     module_info::in, module_info::in, module_info::out,
     rev_proc_map::in, rev_proc_map::out,
-    ts_string_table::in, ts_string_table::out) is det.
+    pp_string_table::in, pp_string_table::out) is det.
 
 add_requested_specialized_par_proc(CallPattern, NewProc, !PendingParProcs,
         !Pushability, DoneParProcs, InitialModuleInfo, !ModuleInfo,
-        !RevProcMap, !TSStringTable) :-
+        !RevProcMap, !PPStringTable) :-
     CallPattern = par_proc_call_pattern(OldPredProcId, FutureArgs),
     NewProc = new_par_proc(NewPredProcId, _Name),
     OldPredProcId = proc(OldPredId, OldProcId),
@@ -1697,7 +1697,7 @@ add_requested_specialized_par_proc(CallPattern, NewProc, !PendingParProcs,
         % placeholder) specialized procedure.
         IgnoreVars = set_of_var.sorted_list_to_set(map.keys(FutureMap)),
         sync_dep_par_conjs_in_proc(NewPredId, NewProcId, IgnoreVars,
-            !ModuleInfo, [], _ProcsToScan, !TSStringTable),
+            !ModuleInfo, [], _ProcsToScan, !PPStringTable),
         find_specialization_requests_in_proc(DoneParProcs, InitialModuleInfo,
             NewPredProcId, !ModuleInfo, !PendingParProcs, !Pushability,
             !RevProcMap)
@@ -3108,17 +3108,17 @@ seen_more_signal_2(seen_signal_non_negligible_cost_after,
     %
 :- pred allocate_future(module_info::in, prog_var::in, hlds_goals::out,
     prog_varset::in, prog_varset::out, vartypes::in, vartypes::out,
-    future_map::in, future_map::out, ts_string_table::in, ts_string_table::out)
+    future_map::in, future_map::out, pp_string_table::in, pp_string_table::out)
     is det.
 
 allocate_future(ModuleInfo, SharedVar, Goals, !VarSet, !VarTypes,
-        !FutureMap, !TSStringTable) :-
+        !FutureMap, !PPStringTable) :-
     lookup_var_type(!.VarTypes, SharedVar, SharedVarType),
     varset.lookup_name(!.VarSet, SharedVar, SharedVarName),
     make_future_var(SharedVarName, SharedVarType, FutureVar, FutureVarType,
         !VarSet, !VarTypes),
     make_future_name_var_and_goal(SharedVarName, FutureNameVar, SetNameGoal,
-        !VarSet, !VarTypes, !TSStringTable),
+        !VarSet, !VarTypes, !PPStringTable),
     map.det_insert(SharedVar, FutureVar, !FutureMap),
 
     ModuleName = mercury_par_builtin_module,
@@ -3164,13 +3164,14 @@ make_future_var(SharedVarName, SharedVarType, FutureVar, FutureVarType,
 
 :- pred make_future_name_var_and_goal(string::in, prog_var::out, hlds_goal::out,
     prog_varset::in, prog_varset::out, vartypes::in, vartypes::out,
-    ts_string_table::in, ts_string_table::out) is det.
+    pp_string_table::in, pp_string_table::out) is det.
 
-make_future_name_var_and_goal(Name, FutureNameVar, Goal, !VarSet, !VarTypes, !TSStringTable) :-
+make_future_name_var_and_goal(Name, FutureNameVar, Goal, !VarSet, !VarTypes,
+        !PPStringTable) :-
     varset.new_named_var("FutureName" ++ Name, FutureNameVar, !VarSet),
     IntType = builtin_type(builtin_type_int),
     add_var_type(FutureNameVar, IntType, !VarTypes),
-    allocate_ts_string(Name, NameId, !TSStringTable),
+    allocate_pp_string(Name, NameId, !PPStringTable),
     Ground = ground(unique, none),
     GoalExpr = unify(FutureNameVar, rhs_functor(int_const(NameId), no, []),
         (free(IntType) -> Ground) - (Ground -> Ground),
@@ -3303,7 +3304,7 @@ signal_future_pred_name = "signal_future".
 :- func new_future_code = string.
 
 new_future_code = "
-    #ifdef MR_THREADSCOPE
+    #ifdef MR_PARPROF
         MR_par_builtin_new_future(Name, Future);
     #else
         MR_par_builtin_new_future(Future);
@@ -3471,21 +3472,21 @@ var_not_in_nonlocals(Var, Goal) :-
 
 %-----------------------------------------------------------------------------%
 %
-% Threadscope support used in this module.
+% Code used within this module for profiling parallel Mercury programs.
 %
 
-:- type ts_string_table
-    --->    ts_string_table(
-                st_lookup_map       :: map(string, int),
-                st_rev_table        :: list(string),
-                st_size             :: int
+:- type pp_string_table
+    --->    pp_string_table(
+                pp_lookup_map       :: map(string, int),
+                pp_rev_table        :: list(string),
+                pp_size             :: int
             ).
 
-:- pred allocate_ts_string(string::in, int::out,
-    ts_string_table::in, ts_string_table::out) is det.
+:- pred allocate_pp_string(string::in, int::out,
+    pp_string_table::in, pp_string_table::out) is det.
 
-allocate_ts_string(String, Id, !Table) :-
-    !.Table = ts_string_table(Map0, RevTable0, Size0),
+allocate_pp_string(String, Id, !Table) :-
+    !.Table = pp_string_table(Map0, RevTable0, Size0),
     ( map.search(Map0, String, ExistingId) ->
         Id = ExistingId
     ;
@@ -3493,20 +3494,20 @@ allocate_ts_string(String, Id, !Table) :-
         Size = Size0 + 1,
         RevTable = [String | RevTable0],
         map.det_insert(String, Id, Map0, Map),
-        !:Table = ts_string_table(Map, RevTable, Size)
+        !:Table = pp_string_table(Map, RevTable, Size)
     ).
 
-:- pred make_ts_string_table(list(string)::in, ts_string_table::out) is det.
+:- pred make_pp_string_table(list(string)::in, pp_string_table::out) is det.
 
-make_ts_string_table(RevTable, ts_string_table(Map, RevTable, Size)) :-
-    make_ts_string_table_2(RevTable, Size, map.init, Map).
+make_pp_string_table(RevTable, pp_string_table(Map, RevTable, Size)) :-
+    make_pp_string_table_2(RevTable, Size, map.init, Map).
 
-:- pred make_ts_string_table_2(list(string)::in, int::out,
+:- pred make_pp_string_table_2(list(string)::in, int::out,
     map(string, int)::in, map(string, int)::out) is det.
 
-make_ts_string_table_2([], 0, !Map).
-make_ts_string_table_2([Str | Strs], Size, !Map) :-
-    make_ts_string_table_2(Strs, Size0, !Map),
+make_pp_string_table_2([], 0, !Map).
+make_pp_string_table_2([Str | Strs], Size, !Map) :-
+    make_pp_string_table_2(Strs, Size0, !Map),
     Size = Size0 + 1,
     map.det_insert(Str, Size0, !Map).
 
diff --git a/compiler/global_data.m b/compiler/global_data.m
index 6519d58..9124f5d 100644
--- a/compiler/global_data.m
+++ b/compiler/global_data.m
@@ -63,13 +63,13 @@
 :- pred global_data_get_all_closure_layouts(global_data::in,
     list(closure_proc_id_data)::out) is det.
 
-:- pred global_data_get_threadscope_string_table(global_data::in,
+:- pred global_data_get_parprof_string_table(global_data::in,
     list(string)::out) is det.
 
-:- pred global_data_get_threadscope_rev_string_table(global_data::in,
+:- pred global_data_get_parprof_rev_string_table(global_data::in,
     list(string)::out, int::out) is det.
 
-:- pred global_data_set_threadscope_rev_string_table(list(string)::in, int::in,
+:- pred global_data_set_parprof_rev_string_table(list(string)::in, int::in,
     global_data::in, global_data::out) is det.
 
 :- pred global_data_get_static_cell_info(global_data::in,
@@ -185,13 +185,13 @@
                 gd_closure_layouts          :: list(closure_proc_id_data),
 
                 % A table for allocating and maintaining slots where string IDs
-                % will be placed at runtime for threadscope profiling.  The
+                % will be placed at runtime for parallel profiling.  The
                 % actual string IDs are allocated at runtime and their IDs are
                 % placed in an array slot which can be referred to statically.
                 % The size of the table is maintained for allocating offsets
                 % into it.
-                gd_ts_string_table_size     :: int,
-                gd_ts_rev_string_table      :: list(string),
+                gd_pp_string_table_size     :: int,
+                gd_pp_rev_string_table      :: list(string),
 
                 % Information about all the statically allocated cells
                 % created so far.
@@ -248,19 +248,19 @@ global_data_get_all_proc_layouts(GlobalData, ProcLayouts) :-
 global_data_get_all_closure_layouts(GlobalData, ClosureLayouts) :-
     ClosureLayouts = GlobalData ^ gd_closure_layouts.
 
-global_data_get_threadscope_string_table(GlobalData, Table) :-
-    global_data_get_threadscope_rev_string_table(GlobalData, RevTable, _),
+global_data_get_parprof_string_table(GlobalData, Table) :-
+    global_data_get_parprof_rev_string_table(GlobalData, RevTable, _),
     Table = list.reverse(RevTable).
 
-global_data_get_threadscope_rev_string_table(GlobalData,
+global_data_get_parprof_rev_string_table(GlobalData,
         RevTable, TableSize) :-
-    RevTable = GlobalData ^ gd_ts_rev_string_table,
-    TableSize = GlobalData ^ gd_ts_string_table_size.
+    RevTable = GlobalData ^ gd_pp_rev_string_table,
+    TableSize = GlobalData ^ gd_pp_string_table_size.
 
-global_data_set_threadscope_rev_string_table(RevTable, TableSize,
+global_data_set_parprof_rev_string_table(RevTable, TableSize,
         !GlobalData) :-
-    !GlobalData ^ gd_ts_rev_string_table := RevTable,
-    !GlobalData ^ gd_ts_string_table_size := TableSize.
+    !GlobalData ^ gd_pp_rev_string_table := RevTable,
+    !GlobalData ^ gd_pp_string_table_size := TableSize.
 
 global_data_get_static_cell_info(GlobalData, StaticCellInfo) :-
     StaticCellInfo = GlobalData ^ gd_static_cell_info.
@@ -746,7 +746,7 @@ merge_global_datas(GlobalDataA, GlobalDataB, GlobalData, GlobalDataRemap) :-
     ProcVarMap = map.old_merge(ProcVarMapA, ProcVarMapB),
     ProcLayoutMap = map.old_merge(ProcLayoutMapA, ProcLayoutMapB),
     ClosureLayouts = ClosureLayoutsA ++ ClosureLayoutsB,
-    merge_threadscope_string_tables(TSRevStringTableA, TSStringSlotCounterA,
+    merge_parprof_string_tables(TSRevStringTableA, TSStringSlotCounterA,
         TSRevStringTableB, TSStringSlotCounterB,
         TSRevStringTable, TSStringSlotCounter, MaybeTSStringTableRemap),
     merge_static_cell_infos(StaticCellInfoA, StaticCellInfoB, StaticCellInfo,
@@ -757,23 +757,23 @@ merge_global_datas(GlobalDataA, GlobalDataB, GlobalData, GlobalDataRemap) :-
     GlobalDataRemap =
         global_data_remapping(MaybeTSStringTableRemap, StaticCellRemap).
 
-    % merge_threadscope_string_tables(RevTableA, CounterA, RevTableB, CounterB,
+    % merge_parprof_string_tables(RevTableA, CounterA, RevTableB, CounterB,
     %   RevTable, Counter, MaybeRemapOffset).
     %
-    % Merge the threadscope string tables.
+    % Merge the parprof string tables.
     %
     % After doing this merge the references in RevTableB may be adjusted and
     % must be corrected by adding RemapOffset to them if MaybeRemapOffset =
     % yes(RemapOffset).
     %
-:- pred merge_threadscope_string_tables(list(string)::in, int::in,
+:- pred merge_parprof_string_tables(list(string)::in, int::in,
     list(string)::in, int::in,
     list(string)::out, int::out, maybe(int)::out) is det.
 
-merge_threadscope_string_tables([], _, [], _, [], 0, no).
-merge_threadscope_string_tables([], _, [X | Xs], N, [X | Xs], N, no).
-merge_threadscope_string_tables([X | Xs], N, [], _, [X | Xs], N, no).
-merge_threadscope_string_tables(RevTableA, CounterA, RevTableB, CounterB,
+merge_parprof_string_tables([], _, [], _, [], 0, no).
+merge_parprof_string_tables([], _, [X | Xs], N, [X | Xs], N, no).
+merge_parprof_string_tables([X | Xs], N, [], _, [X | Xs], N, no).
+merge_parprof_string_tables(RevTableA, CounterA, RevTableB, CounterB,
         RevTable, Counter, yes(RemapOffset)) :-
     RevTableA = [_ | _],
     RevTableB = [_ | _],
diff --git a/compiler/hlds_module.m b/compiler/hlds_module.m
index cf7f3e3..1597498 100644
--- a/compiler/hlds_module.m
+++ b/compiler/hlds_module.m
@@ -557,10 +557,10 @@
 :- pred module_info_set_const_struct_db(const_struct_db::in,
     module_info::in, module_info::out) is det.
 
-:- pred module_info_get_ts_rev_string_table(module_info::in, int::out,
+:- pred module_info_get_parprof_rev_string_table(module_info::in, int::out,
     list(string)::out) is det.
 
-:- pred module_info_set_ts_rev_string_table(int::in, list(string)::in,
+:- pred module_info_set_parprof_rev_string_table(int::in, list(string)::in,
     module_info::in, module_info::out) is det.
 
 %-----------------------------------------------------------------------------%
@@ -880,14 +880,14 @@
                 % of the program.
                 msi_const_struct_db             :: const_struct_db,
 
-                % A table of strings used by some threadscope events.
-                % Currently threadscope events are introduced for each future
-                % in dep_par_conj.m which is why we need to record the table
-                % within the HLDS.  The LLDS also uses threadscope string
-                % tables, see global_data.m, the LLDS introduces strings during
-                % the HLDS->LLDS transformation of parallel conjunctions.
-                msi_ts_string_table_size        :: int,
-                msi_ts_rev_string_table         :: list(string)
+                % A table of strings used by some parallel profiling events.
+                % Currently these events are introduced for each future in
+                % dep_par_conj.m which is why we need to record the table
+                % within the HLDS.  The LLDS also uses these string tables,
+                % see global_data.m, the LLDS introduces strings during the
+                % HLDS->LLDS transformation of parallel conjunctions.
+                msi_pp_string_table_size        :: int,
+                msi_pp_rev_string_table         :: list(string)
             ).
 
 module_info_init(Name, DumpBaseFileName, Items, Globals, QualifierInfo,
@@ -1096,9 +1096,9 @@ module_info_get_event_set(MI, MI ^ mi_sub_info ^ msi_event_set).
 module_info_get_oisu_map(MI, MI ^ mi_sub_info ^ msi_oisu_map).
 module_info_get_oisu_procs(MI, MI ^ mi_sub_info ^ msi_oisu_procs).
 module_info_get_const_struct_db(MI, MI ^ mi_sub_info ^ msi_const_struct_db).
-module_info_get_ts_rev_string_table(MI,
-    MI ^ mi_sub_info ^ msi_ts_string_table_size,
-    MI ^ mi_sub_info ^ msi_ts_rev_string_table).
+module_info_get_parprof_rev_string_table(MI,
+    MI ^ mi_sub_info ^ msi_pp_string_table_size,
+    MI ^ mi_sub_info ^ msi_pp_rev_string_table).
 
     % XXX There is some debate as to whether duplicate initialise directives
     % in the same module should constitute an error. Currently it is not, but
@@ -1261,9 +1261,9 @@ module_info_set_oisu_procs(OISUProcs, !MI) :-
     !MI ^ mi_sub_info ^ msi_oisu_procs := OISUProcs.
 module_info_set_const_struct_db(ConstStructDb, !MI) :-
     !MI ^ mi_sub_info ^ msi_const_struct_db := ConstStructDb.
-module_info_set_ts_rev_string_table(Size, RevTable, !MI) :-
-    !MI ^ mi_sub_info ^ msi_ts_string_table_size := Size,
-    !MI ^ mi_sub_info ^ msi_ts_rev_string_table := RevTable.
+module_info_set_parprof_rev_string_table(Size, RevTable, !MI) :-
+    !MI ^ mi_sub_info ^ msi_pp_string_table_size := Size,
+    !MI ^ mi_sub_info ^ msi_pp_rev_string_table := RevTable.
 
 module_info_add_parents_to_used_modules(Modules, !MI) :-
     module_info_get_used_modules(!.MI, UsedModules0),
diff --git a/compiler/layout.m b/compiler/layout.m
index b801d10..25e6dcf 100644
--- a/compiler/layout.m
+++ b/compiler/layout.m
@@ -359,7 +359,7 @@
     ;       proc_table_io_decl_array
     ;       proc_event_layouts_array
     ;       proc_exec_trace_array
-    ;       threadscope_string_table_array
+    ;       parprof_string_table_array
     ;       alloc_site_array.
 
 %-----------------------------------------------------------------------------%
diff --git a/compiler/layout_out.m b/compiler/layout_out.m
index 5f6339a..ad3355e 100644
--- a/compiler/layout_out.m
+++ b/compiler/layout_out.m
@@ -502,7 +502,7 @@ output_layout_array_defns(Info, PseudoTypeInfos, HLDSVarNums,
         TSStringTable = []
     ;
         TSStringTable = [_ | _],
-        output_threadscope_string_table_array(Info, TSStringTable, !IO)
+        output_parprof_string_table_array(Info, TSStringTable, !IO)
     ),
     (
         AllocSites = []
@@ -1596,28 +1596,29 @@ eval_method_to_c_string(eval_table_io(Decl, Unitize)) = Str :-
 
 %-----------------------------------------------------------------------------%
 %
-% Definition of array #20: threadscope string table.
+% Definition of array #20: parallel profiling (formerly threadscope) string
+% table.
 %
 
-:- pred output_threadscope_string_table_array(llds_out_info::in,
+:- pred output_parprof_string_table_array(llds_out_info::in,
     list(string)::in, io::di, io::uo) is det.
 
-output_threadscope_string_table_array(Info, TSStringTable, !IO) :-
+output_parprof_string_table_array(Info, StringTable, !IO) :-
     ModuleName = Info ^ lout_mangled_module_name,
-    list.length(TSStringTable, NumStrings),
-    Name = threadscope_string_table_array,
-    io.write_string("#ifdef MR_THREADSCOPE\n", !IO),
+    list.length(StringTable, NumStrings),
+    Name = parprof_string_table_array,
+    io.write_string("#ifdef MR_PARPROF\n", !IO),
     output_layout_array_name_storage_type_name(ModuleName, Name,
         being_defined, !IO),
     io.format("[%d] = {\n", [i(NumStrings)], !IO),
-    list.foldl2(output_threadscope_string_table_slot(Info), TSStringTable,
+    list.foldl2(output_parprof_string_table_slot(Info), StringTable,
         0, _, !IO),
     io.write_string("};\n#endif\n\n", !IO).
 
-:- pred output_threadscope_string_table_slot(llds_out_info::in, string::in,
+:- pred output_parprof_string_table_slot(llds_out_info::in, string::in,
     int::in, int::out, io::di, io::uo) is det.
 
-output_threadscope_string_table_slot(Info, String, !Slot, !IO) :-
+output_parprof_string_table_slot(Info, String, !Slot, !IO) :-
     AutoComments = Info ^ lout_auto_comments,
     (
         AutoComments = yes,
@@ -1753,8 +1754,8 @@ output_layout_array_name(UseMacro, ModuleName, ArrayName, !IO) :-
             ArrayName = proc_exec_trace_array,
             io.write_string("MR_proc_exec_traces", !IO)
         ;
-            ArrayName = threadscope_string_table_array,
-            io.write_string("MR_threadscope_strings", !IO)
+            ArrayName = parprof_string_table_array,
+            io.write_string("MR_parprof_strings", !IO)
         ;
             ArrayName = alloc_site_array,
             io.write_string("MR_alloc_sites", !IO)
@@ -1822,8 +1823,8 @@ output_layout_array_name(UseMacro, ModuleName, ArrayName, !IO) :-
             ArrayName = proc_exec_trace_array,
             io.write_string("mercury_data__proc_exec_traces_array__", !IO)
         ;
-            ArrayName = threadscope_string_table_array,
-            io.write_string("mercury_data__threadscope_string_table_array__",
+            ArrayName = parprof_string_table_array,
+            io.write_string("mercury_data__parprof_string_table_array__",
                 !IO)
         ;
             ArrayName = alloc_site_array,
@@ -2094,8 +2095,8 @@ output_layout_array_name_storage_type_name(ModuleName, Name, BeingDefined,
         output_layout_array_name(do_not_use_layout_macro, ModuleName,
             Name, !IO)
     ;
-        Name = threadscope_string_table_array,
-        io.write_string("MR_Threadscope_String ", !IO),
+        Name = parprof_string_table_array,
+        io.write_string("MR_Parprof_String ", !IO),
         output_layout_array_name(do_not_use_layout_macro, ModuleName,
             Name, !IO)
     ;
@@ -3277,7 +3278,7 @@ output_layout_slots_in_vector(ModuleName, [SlotName | SlotNames], !IO) :-
         ; ArrayName = proc_table_io_decl_array
         ; ArrayName = proc_event_layouts_array
         ; ArrayName = proc_exec_trace_array
-        ; ArrayName = threadscope_string_table_array
+        ; ArrayName = parprof_string_table_array
         ; ArrayName = alloc_site_array
         ),
         output_layout_slot_addr(use_layout_macro, ModuleName, SlotName, !IO),
diff --git a/compiler/llds.m b/compiler/llds.m
index 4a9c0c2..b0b986b 100644
--- a/compiler/llds.m
+++ b/compiler/llds.m
@@ -642,7 +642,7 @@
             % address of the synchronization term.  The second argument
             % indicates how many branches we expect to join at the end of the
             % parallel conjunction.  The third argument is an index into the
-            % threadscope string table.  The string that it refers to
+            % parallel profiling string table.  The string that it refers to
             % identifies this parallel conjunction within the source code.
             % (See the documentation in par_conj_gen.m and
             % runtime/mercury_context.{c,h} for further information about
diff --git a/compiler/llds_out_file.m b/compiler/llds_out_file.m
index 9018d9a..e91d345 100644
--- a/compiler/llds_out_file.m
+++ b/compiler/llds_out_file.m
@@ -399,7 +399,7 @@ gather_labels_from_instrs_acc([Instr | Instrs],
     decl_set::in, decl_set::out, io::di, io::uo) is det.
 
 output_c_module_init_list(Info, ModuleName, AnnotatedModules, RttiDatas,
-        ProcLayoutDatas, ModuleLayoutDatas, ComplexityProcs, TSStringTable,
+        ProcLayoutDatas, ModuleLayoutDatas, ComplexityProcs, PPStringTable,
         AllocSites, InitPredNames, FinalPredNames, !DeclSet, !IO) :-
     MustInit = (pred(Module::in) is semidet :-
         module_defines_label_with_layout(Info, Module)
@@ -446,10 +446,10 @@ output_c_module_init_list(Info, ModuleName, AnnotatedModules, RttiDatas,
     io.write_string("init_complexity_procs(void);\n", !IO),
     io.write_string("#endif\n", !IO),
 
-    io.write_string("#ifdef MR_THREADSCOPE\n", !IO),
+    io.write_string("#ifdef MR_PARPROF\n", !IO),
     io.write_string("void ", !IO),
     output_init_name(ModuleName, !IO),
-    io.write_string("init_threadscope_string_table(void);\n", !IO),
+    io.write_string("init_parprof_string_table(void);\n", !IO),
     io.write_string("#endif\n", !IO),
 
     (
@@ -555,22 +555,22 @@ output_c_module_init_list(Info, ModuleName, AnnotatedModules, RttiDatas,
     io.write_string("}\n", !IO),
     io.write_string("\n#endif\n\n", !IO),
 
-    io.write_string("#ifdef MR_THREADSCOPE\n", !IO),
+    io.write_string("#ifdef MR_PARPROF\n", !IO),
     io.write_string("\nvoid ", !IO),
     output_init_name(ModuleName, !IO),
-    io.write_string("init_threadscope_string_table(void)\n", !IO),
+    io.write_string("init_parprof_string_table(void)\n", !IO),
     io.write_string("{\n", !IO),
     (
-        TSStringTable = []
+        PPStringTable = []
     ;
-        TSStringTable = [_ | _],
-        TSStringTableSize = length(TSStringTable),
-        io.write_string("\tMR_threadscope_register_strings_array(\n", !IO),
+        PPStringTable = [_ | _],
+        PPStringTableSize = length(PPStringTable),
+        io.write_string("\tMR_parprof_register_strings_array(\n", !IO),
         io.write_string("\t\t", !IO),
         MangledModuleName = Info ^ lout_mangled_module_name,
         output_layout_array_name(use_layout_macro, MangledModuleName,
-            threadscope_string_table_array, !IO),
-        io.format(", %d);\n", [i(TSStringTableSize)], !IO)
+            parprof_string_table_array, !IO),
+        io.format(", %d);\n", [i(PPStringTableSize)], !IO)
     ),
     io.write_string("}\n", !IO),
     io.write_string("\n#endif\n\n", !IO),
diff --git a/compiler/mercury_compile_llds_back_end.m b/compiler/mercury_compile_llds_back_end.m
index ceb3479..537a4ef 100644
--- a/compiler/mercury_compile_llds_back_end.m
+++ b/compiler/mercury_compile_llds_back_end.m
@@ -111,9 +111,9 @@ llds_backend_pass(!HLDS, !:GlobalData, LLDS, !DumpInfo, !IO) :-
     ),
     StaticCellInfo0 = init_static_cell_info(ModuleName, UnboxFloats,
         DoCommonData),
-    module_info_get_ts_rev_string_table(!.HLDS, TSStringTableSize,
-        TSRevStringTable),
-    global_data_init(StaticCellInfo0, TSStringTableSize, TSRevStringTable,
+    module_info_get_parprof_rev_string_table(!.HLDS, PPStringTableSize,
+        PPRevStringTable),
+    global_data_init(StaticCellInfo0, PPStringTableSize, PPRevStringTable,
         !:GlobalData),
 
     globals.lookup_bool_option(Globals, verbose, Verbose),
@@ -641,7 +641,7 @@ llds_output_pass(HLDS, GlobalData0, Procs, ModuleName, Succeeded,
     get_static_cells(StaticCellInfo,
         ScalarCommonCellDatas, VectorCommonCellDatas),
     global_data_get_all_alloc_sites(GlobalData, AllocSites, AllocIdMap),
-    global_data_get_threadscope_string_table(GlobalData, TSStringTable),
+    global_data_get_parprof_string_table(GlobalData, PPStringTable),
 
     % Next we put it all together and output it to one or more C files.
     RttiDatas = TypeCtorRttiData ++ TypeClassInfoRttiData,
@@ -688,7 +688,7 @@ llds_output_pass(HLDS, GlobalData0, Procs, ModuleName, Succeeded,
         NoVarLabelLayouts, SVarLabelLayouts, LVarLabelLayouts,
         InternalLabelToLayoutMap, ProcLabelToLayoutMap,
         CallSites, CoveragePoints, ProcStatics,
-        ProcHeadVarNums, ProcVarNames, ProcBodyBytecodes, TSStringTable,
+        ProcHeadVarNums, ProcVarNames, ProcBodyBytecodes, PPStringTable,
         TableIoDecls, TableIoDeclMap, ProcEventLayouts, ExecTraces,
         ProcLayoutDatas, ModuleLayoutDatas, ClosureLayoutDatas,
         AllocSites, AllocIdMap, ChunkedModules,
diff --git a/compiler/opt_debug.m b/compiler/opt_debug.m
index 7cbf562..e77a67e 100644
--- a/compiler/opt_debug.m
+++ b/compiler/opt_debug.m
@@ -588,8 +588,8 @@ dump_layout_array_name(ArrayName) = Str :-
         ArrayName = proc_table_io_decl_array,
         Str = "proc_table_io_decl_array"
     ;
-        ArrayName = threadscope_string_table_array,
-        Str = "threadscope_string_table_array"
+        ArrayName = parprof_string_table_array,
+        Str = "parprof_string_table_array"
     ;
         ArrayName = alloc_site_array,
         Str = "alloc_site_array"
diff --git a/compiler/par_conj_gen.m b/compiler/par_conj_gen.m
index af8cd13..f7bd2cd 100644
--- a/compiler/par_conj_gen.m
+++ b/compiler/par_conj_gen.m
@@ -227,7 +227,7 @@ generate_par_conj(Goals, GoalInfo, CodeModel, Code, !CI) :-
     EndLabelCode = from_list([
         llds_instr(label(EndLabel), "end of parallel conjunction"),
         llds_instr(ts_finish_par_conj_instr(SlotNum, SyncTermBaseSlot),
-            "finish parallel conjunction (ThreadScope instrumentation")
+            "finish parallel conjunction (parallel profiling instrumentation")
     ]),
     Code =
         MaybeSetParentSpCode ++
@@ -325,8 +325,8 @@ ts_finish_par_conj_instr(SyncTermBaseSlot, SyncTermBaseSlotLval) =
         proc_does_not_affect_liveness,
         live_lvals_info(set([SyncTermBaseSlotLval])),
         format(Code, [i(SyncTermBaseSlot)]))],
-    Code = "#ifdef MR_THREADSCOPE
-MR_threadscope_post_end_par_conj(&MR_sv(%d));
+    Code = "#ifdef MR_PARPROF
+MR_parprof_post_end_par_conj(&MR_sv(%d));
 #endif
 ".
 
@@ -654,7 +654,7 @@ create_static_conj_id(GoalInfo, SlotNum, !CI) :-
     GoalPathString = goal_path_to_string(GoalPath),
 
     String = format("%s: %s", [s(ProcString), s(GoalPathString)]),
-    add_threadscope_string(String, SlotNum, !CI).
+    add_parprof_string(String, SlotNum, !CI).
 
 %----------------------------------------------------------------------------%
 :- end_module ll_backend.par_conj_gen.
diff --git a/compiler/proc_gen.m b/compiler/proc_gen.m
index 71144d8..d041d10 100644
--- a/compiler/proc_gen.m
+++ b/compiler/proc_gen.m
@@ -369,7 +369,7 @@ generate_proc_code(ModuleInfo0, ConstStructMap, PredId, PredInfo,
     % for model_det procedures, always needed for model_semi procedures, and
     % needed for model_non procedures only if we are doing execution tracing.
     global_data_get_static_cell_info(!.GlobalData, StaticCellInfo0),
-    global_data_get_threadscope_rev_string_table(!.GlobalData,
+    global_data_get_parprof_rev_string_table(!.GlobalData,
         TSRevStringTable0, TSStringTableSize0),
 
     code_info_init(SaveSuccip, Globals, PredId, ProcId, PredInfo,
@@ -400,10 +400,10 @@ generate_proc_code(ModuleInfo0, ConstStructMap, PredId, PredInfo,
     get_static_cell_info(CodeInfo, StaticCellInfo),
     global_data_set_static_cell_info(StaticCellInfo, !GlobalData),
 
-    get_threadscope_rev_string_table(CodeInfo,
-        TSRevStringTable, TSStringTableSize),
-    global_data_set_threadscope_rev_string_table(TSRevStringTable,
-        TSStringTableSize, !GlobalData),
+    get_parprof_rev_string_table(CodeInfo,
+        PPRevStringTable, PPStringTableSize),
+    global_data_set_parprof_rev_string_table(PPRevStringTable,
+        PPStringTableSize, !GlobalData),
 
     get_created_temp_frame(CodeInfo, CreatedTempFrame),
     get_proc_trace_events(CodeInfo, ProcTraceEvents),
diff --git a/library/benchmarking.m b/library/benchmarking.m
index 9163a6a..aadd5d8 100644
--- a/library/benchmarking.m
+++ b/library/benchmarking.m
@@ -1313,7 +1313,7 @@ dump_trace_counts_to(_, 1, !IO).
     [will_not_call_mercury, will_not_throw_exception, thread_safe, 
         promise_pure, tabled_for_io],
 "
-#if MR_THREADSCOPE
+#if MR_PARPROF
     MR_threadscope_post_log_msg(Message);
 #endif
 ").
diff --git a/library/par_builtin.m b/library/par_builtin.m
index 6c2b1a5..6a9bfb1 100644
--- a/library/par_builtin.m
+++ b/library/par_builtin.m
@@ -165,7 +165,7 @@
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail,
         may_not_duplicate],
 "
-    #ifdef MR_THREADSCOPE
+    #ifdef MR_PARPROF
         MR_par_builtin_new_future(Future, Name);
     #else
         MR_par_builtin_new_future(Future);
diff --git a/runtime/mercury_atomic_ops.h b/runtime/mercury_atomic_ops.h
index 43d71b0..f8825aa 100644
--- a/runtime/mercury_atomic_ops.h
+++ b/runtime/mercury_atomic_ops.h
@@ -742,7 +742,7 @@ extern MR_uint_least64_t MR_cpu_cycles_per_sec;
 
 /*
 ** Do CPU feature detection, this is necessary for profiling parallel code
-** execution and the threadscope code.
+** execution and the parallel profiling code.
 ** On i386 and x86_64 machines this uses CPUID to determine if the RDTSCP
 ** instruction is available and not prohibited by the OS.
 ** This function is idempotent.
diff --git a/runtime/mercury_conf_param.h b/runtime/mercury_conf_param.h
index fda7817..9d35c13 100644
--- a/runtime/mercury_conf_param.h
+++ b/runtime/mercury_conf_param.h
@@ -222,14 +222,15 @@
 ** MR_THREAD_SAFE
 ** Enable support for parallelism.
 **
-** MR_THREADSCOPE
-** Enable support for parallelism profiling, aka 'threadscope'.  This is a
-** grade component. This works only with the low level C parallel grades.
+** MR_PARPROF
+** Enable support for parallelism profiling, formerlly 'threadscope support'.
+** This is a grade component.  This works only with the low level C parallel
+** grades.
 **
 ** MR_PROFILE_PARALLEL_EXECUTION_SUPPORT
 ** Enable support for profiling the parallel runtime system.  This collects
 ** counts and timings of certain runtime events.  It is implied by
-** MR_THREADSCOPE and must be enabled at runtime with the
+** MR_PARPROF and must be enabled at runtime with the
 ** --profile-parallel-execution runtime option.
 **
 ** MR_NO_BACKWARDS_COMPAT
@@ -937,17 +938,18 @@
 #endif
 
 /*
-** Check that MR_THREADSCOPE is used correctly.
+** Check that MR_PARPROF is used correctly.
 */
-#if defined(MR_THREADSCOPE) && !defined(MR_THREAD_SAFE)
+#if defined(MR_PARPROF) && !defined(MR_THREAD_SAFE)
   #error "The threadscope grade component may only be used with " \
     "parallel grades"
 #endif
 
 #ifdef MR_PROFILE_PARALLEL_EXECUTION_SUPPORT
-  #error "MR_PROFILE_PARALLEL_EXECUTION_SUPPORT may only be implied by MR_THREADSCOPE"
+  #error "MR_PROFILE_PARALLEL_EXECUTION_SUPPORT may only be implied by "
+    "MR_PARPROF"
 #endif
-#ifdef MR_THREADSCOPE
+#ifdef MR_PARPROF
   #define MR_PROFILE_PARALLEL_EXECUTION_SUPPORT
 #endif
 
diff --git a/runtime/mercury_context.c b/runtime/mercury_context.c
index 37200a9..9d40f4b 100644
--- a/runtime/mercury_context.c
+++ b/runtime/mercury_context.c
@@ -1110,11 +1110,11 @@ MR_create_context(const char *id, MR_ContextSize ctxt_size, MR_Generator *gen)
     MR_UNLOCK(&free_context_list_lock, "create_context i");
 
     if (c != NULL) {
-#ifdef MR_THREADSCOPE
+#ifdef MR_PARPROF
         MR_Unsigned old_id = c->MR_ctxt_num_id;
 
         c->MR_ctxt_num_id = allocate_context_id();
-        MR_threadscope_post_reuse_context(c, old_id);
+        MR_parprof_post_reuse_context(c, old_id);
 #endif
 #ifdef MR_DEBUG_STACK_SEGMENTS
         MR_debug_log_message("Re-used an old context: %p", c);
@@ -1135,9 +1135,9 @@ MR_create_context(const char *id, MR_ContextSize ctxt_size, MR_Generator *gen)
 #ifdef MR_USE_TRAIL
         c->MR_ctxt_trail_zone = NULL;
 #endif
-#ifdef MR_THREADSCOPE
+#ifdef MR_PARPROF
         c->MR_ctxt_num_id = allocate_context_id();
-        MR_threadscope_post_create_context(c);
+        MR_parprof_post_create_context(c);
 #endif
     }
 
@@ -1156,8 +1156,8 @@ MR_release_context(MR_Context *c)
 {
     MR_assert(c);
 
-#ifdef MR_THREADSCOPE
-    MR_threadscope_post_release_context(c);
+#ifdef MR_PARPROF
+    MR_parprof_post_release_context(c);
 #endif
 
 #ifdef MR_THREAD_SAFE
@@ -1552,7 +1552,7 @@ MR_schedule_context(MR_Context *ctxt)
     notify_context_data.MR_ewa_context = ctxt;
 
 #ifdef MR_PROFILE_PARALLEL_EXECUTION_SUPPORT
-    MR_threadscope_post_context_runnable(ctxt);
+    MR_parprof_post_context_runnable(ctxt);
 #endif
 
     /*
@@ -2219,8 +2219,8 @@ MR_define_entry(MR_do_sleep);
         }
 #endif
 
-#ifdef MR_THREADSCOPE
-        MR_threadscope_post_engine_sleeping();
+#ifdef MR_PARPROF
+        MR_parprof_post_engine_sleeping();
 #endif
 
 retry_sleep:
@@ -2422,8 +2422,8 @@ action_worksteal(MR_EngineId victim_engine_id)
         ** Steal from this engine next time, it may have more work.
         */
         MR_ENGINE(MR_eng_victim_counter) = victim_engine_id;
-#ifdef MR_THREADSCOPE
-        MR_threadscope_post_steal_spark(spark.MR_spark_id);
+#ifdef MR_PARPROF
+        MR_parprof_post_steal_spark(spark.MR_spark_id);
 #endif
 #ifdef MR_DEBUG_THREADS
         if (MR_debug_threads) {
@@ -2485,8 +2485,8 @@ do_get_context(void)
     ** context, then proceed to MR_do_runnext_local.
     */
 
-    #ifdef MR_THREADSCOPE
-    MR_threadscope_post_looking_for_global_context();
+    #ifdef MR_PARPROF
+    MR_parprof_post_looking_for_global_context();
     #endif
 
     /*
@@ -2542,8 +2542,8 @@ prepare_engine_for_context(MR_Context *context) {
     }
     MR_ENGINE(MR_eng_this_context) = context;
     MR_load_context(context);
-#ifdef MR_THREADSCOPE
-    MR_threadscope_post_run_context();
+#ifdef MR_PARPROF
+    MR_parprof_post_run_context();
 #endif
 }
 
@@ -2561,8 +2561,8 @@ prepare_engine_for_spark(volatile MR_Spark *spark)
 #endif
         MR_ENGINE(MR_eng_this_context) = MR_create_context("from spark",
             MR_CONTEXT_SIZE_FOR_SPARK, NULL);
-#ifdef MR_THREADSCOPE
-        MR_threadscope_post_create_context_for_spark(
+#ifdef MR_PARPROF
+        MR_parprof_post_create_context_for_spark(
             MR_ENGINE(MR_eng_this_context));
 #endif
 /*
@@ -2579,17 +2579,17 @@ prepare_engine_for_spark(volatile MR_Spark *spark)
             MR_ENGINE(MR_eng_this_context));
 #endif
     } else {
-#ifdef MR_THREADSCOPE
+#ifdef MR_PARPROF
         MR_Unsigned old_id;
 
         old_id = MR_ENGINE(MR_eng_this_context)->MR_ctxt_num_id;
         MR_ENGINE(MR_eng_this_context)->MR_ctxt_num_id = allocate_context_id();
-        MR_threadscope_post_reuse_context(MR_ENGINE(MR_eng_this_context),
+        MR_parprof_post_reuse_context(MR_ENGINE(MR_eng_this_context),
             old_id);
 #endif
     }
-#ifdef MR_THREADSCOPE
-    MR_threadscope_post_run_context();
+#ifdef MR_PARPROF
+    MR_parprof_post_run_context();
 #endif
 
     /*
@@ -2609,8 +2609,8 @@ do_local_spark(MR_Code *join_label)
     volatile MR_Spark *spark;
     MR_Context        *this_context = MR_ENGINE(MR_eng_this_context);
 
-#ifdef MR_THREADSCOPE
-    MR_threadscope_post_looking_for_local_spark();
+#ifdef MR_PARPROF
+    MR_parprof_post_looking_for_local_spark();
 #endif
 
     spark = MR_wsdeque_pop_bottom(&MR_ENGINE(MR_eng_spark_deque));
@@ -2637,8 +2637,8 @@ do_local_spark(MR_Code *join_label)
         return NULL;
     }
 
-#ifdef MR_THREADSCOPE
-    MR_threadscope_post_run_spark(spark->MR_spark_id);
+#ifdef MR_PARPROF
+    MR_parprof_post_run_spark(spark->MR_spark_id);
 #endif
 
     prepare_engine_for_spark(spark);
@@ -2651,8 +2651,8 @@ do_work_steal(void)
 {
     MR_Spark spark;
 
-    #ifdef MR_THREADSCOPE
-    MR_threadscope_post_work_stealing();
+    #ifdef MR_PARPROF
+    MR_parprof_post_work_stealing();
     #endif
 
     /*
@@ -2664,8 +2664,8 @@ do_work_steal(void)
         (MR_num_outstanding_contexts <= MR_max_outstanding_contexts)) {
         /* Attempt to steal a spark */
         if (MR_attempt_steal_spark(&spark)) {
-#ifdef MR_THREADSCOPE
-            MR_threadscope_post_steal_spark(spark.MR_spark_id);
+#ifdef MR_PARPROF
+            MR_parprof_post_steal_spark(spark.MR_spark_id);
 #endif
 #ifdef MR_DEBUG_THREADS
             if (MR_debug_threads) {
@@ -2686,8 +2686,8 @@ static void
 save_dirty_context(MR_Code *join_label) {
     MR_Context *this_context = MR_ENGINE(MR_eng_this_context);
 
-#ifdef MR_THREADSCOPE
-    MR_threadscope_post_stop_context(MR_TS_STOP_REASON_BLOCKED);
+#ifdef MR_PARPROF
+    MR_parprof_post_stop_context(MR_PARPROF_STOP_REASON_BLOCKED);
 #endif
     this_context->MR_ctxt_resume_owner_engine = MR_ENGINE(MR_eng_id);
     MR_save_context(this_context);
@@ -2711,8 +2711,8 @@ MR_do_join_and_continue(MR_SyncTerm *jnc_st, MR_Code *join_label)
     MR_Context  *this_context = MR_ENGINE(MR_eng_this_context);
     MR_Code     *jump_target;
 
-  #ifdef MR_THREADSCOPE
-    MR_threadscope_post_end_par_conjunct((MR_Word*)jnc_st);
+  #ifdef MR_PARPROF
+    MR_parprof_post_end_par_conjunct((MR_Word*)jnc_st);
   #endif
 
     /*
@@ -2722,8 +2722,8 @@ MR_do_join_and_continue(MR_SyncTerm *jnc_st, MR_Code *join_label)
     */
     /*
     ** XXX: We should take the current TSC time here and use it to post the
-    ** various 'context stopped' threadscope events. This profile will be more
-    ** accurate.
+    ** various 'context stopped' parallel profiling events. This profile
+    ** will be more accurate.
     */
 
     jnc_last = MR_atomic_dec_and_is_zero_uint(&(jnc_st->MR_st_count));
@@ -2733,8 +2733,8 @@ MR_do_join_and_continue(MR_SyncTerm *jnc_st, MR_Code *join_label)
         ** All the conjuncts have finished,
         */
         if (this_context != jnc_st->MR_st_orig_context) {
-#ifdef MR_THREADSCOPE
-            MR_threadscope_post_stop_context(MR_TS_STOP_REASON_FINISHED);
+#ifdef MR_PARPROF
+            MR_parprof_post_stop_context(MR_PARPROF_STOP_REASON_FINISHED);
 #endif
             /*
             ** This context didn't originate this parallel conjunction and
@@ -2756,8 +2756,8 @@ MR_do_join_and_continue(MR_SyncTerm *jnc_st, MR_Code *join_label)
             ** the context is written first.
             */
             MR_CPU_LFENCE;
-#ifdef MR_THREADSCOPE
-            MR_threadscope_post_context_runnable(jnc_st->MR_st_orig_context);
+#ifdef MR_PARPROF
+            MR_parprof_post_context_runnable(jnc_st->MR_st_orig_context);
 #endif
             prepare_engine_for_context(jnc_st->MR_st_orig_context);
             /*
@@ -2773,8 +2773,8 @@ MR_do_join_and_continue(MR_SyncTerm *jnc_st, MR_Code *join_label)
     } else {
         volatile MR_Spark *spark;
 
-#ifdef MR_THREADSCOPE
-        MR_threadscope_post_looking_for_local_spark();
+#ifdef MR_PARPROF
+        MR_parprof_post_looking_for_local_spark();
 #endif
         spark = MR_wsdeque_pop_bottom(&MR_ENGINE(MR_eng_spark_deque));
         if (spark != NULL) {
@@ -2785,8 +2785,8 @@ MR_do_join_and_continue(MR_SyncTerm *jnc_st, MR_Code *join_label)
                 **
                 ** Change the context.
                 */
-#ifdef MR_THREADSCOPE
-                MR_threadscope_post_stop_context(MR_TS_STOP_REASON_BLOCKED);
+#ifdef MR_PARPROF
+                MR_parprof_post_stop_context(MR_PARPROF_STOP_REASON_BLOCKED);
 #endif
                 save_dirty_context(join_label);
                 if (MR_runqueue_head != NULL) {
@@ -2807,16 +2807,16 @@ MR_do_join_and_continue(MR_SyncTerm *jnc_st, MR_Code *join_label)
                 /*
                 ** Save our context and then look for work as per normal.
                 */
-#ifdef MR_THREADSCOPE
-                MR_threadscope_post_stop_context(MR_TS_STOP_REASON_BLOCKED);
+#ifdef MR_PARPROF
+                MR_parprof_post_stop_context(MR_PARPROF_STOP_REASON_BLOCKED);
 #endif
                 save_dirty_context(join_label);
             } else {
                 /*
                 ** This engine and context should look for other work.
                 */
-#ifdef MR_THREADSCOPE
-                MR_threadscope_post_stop_context(MR_TS_STOP_REASON_FINISHED);
+#ifdef MR_PARPROF
+                MR_parprof_post_stop_context(MR_PARPROF_STOP_REASON_FINISHED);
 #endif
             }
             return MR_ENTRY(MR_do_idle);
diff --git a/runtime/mercury_context.h b/runtime/mercury_context.h
index 47cb294..433d96b 100644
--- a/runtime/mercury_context.h
+++ b/runtime/mercury_context.h
@@ -253,7 +253,7 @@ struct MR_Spark_Struct {
     MR_SyncTerm             *MR_spark_sync_term;
     MR_Code                 *MR_spark_resume;
     MR_ThreadLocalMuts      *MR_spark_thread_local_mutables;
-#ifdef MR_THREADSCOPE
+#ifdef MR_PARPROF
     MR_uint_least32_t       MR_spark_id;
 #endif
 };
@@ -278,7 +278,7 @@ struct MR_SparkDeque_Struct {
 
 struct MR_Context_Struct {
     const char          *MR_ctxt_id;
-#ifdef MR_THREADSCOPE
+#ifdef MR_PARPROF
     MR_Unsigned         MR_ctxt_num_id;
 #endif
     MR_ContextSize      MR_ctxt_size;
@@ -619,10 +619,10 @@ extern  void        MR_schedule_context(MR_Context *ctxt);
   #define MR_IF_NOT_HIGHLEVEL_CODE(x)
 #endif
 
-#ifdef MR_THREADSCOPE
-  #define MR_IF_THREADSCOPE(x) x
+#ifdef MR_PARPROF
+  #define MR_IF_PARPROF(x) x
 #else
-  #define MR_IF_THREADSCOPE(x)
+  #define MR_IF_PARPROF(x)
 #endif
 
 #ifdef MR_WORKSTEAL_POLLING
@@ -792,7 +792,7 @@ extern  void        MR_schedule_context(MR_Context *ctxt);
   MR_STATIC_ASSERT(mercury_context,
     MR_SYNC_TERM_SIZE == MR_bytes_to_words(sizeof(struct MR_SyncTerm_Struct)));
 
-#ifdef MR_THREADSCOPE
+#ifdef MR_PARPROF
   #define MR_init_sync_term(sync_term, nbranches, static_conj_id)             \
     do {                                                                      \
         MR_SyncTerm *init_st = (MR_SyncTerm *) &(sync_term);                  \
@@ -800,7 +800,7 @@ extern  void        MR_schedule_context(MR_Context *ctxt);
         init_st->MR_st_orig_context = MR_ENGINE(MR_eng_this_context);         \
         init_st->MR_st_parent_sp = MR_parent_sp;                              \
         init_st->MR_st_count = (nbranches);                                   \
-        MR_threadscope_post_start_par_conj(&(sync_term), static_conj_id);     \
+        MR_parprof_post_start_par_conj(&(sync_term), static_conj_id);         \
     } while (0)
 #else
   #define MR_init_sync_term(sync_term, nbranches, static_conj_id)             \
@@ -826,7 +826,7 @@ do {                                                                         \
     MR_Spark            fnc_spark;                                           \
     MR_SparkDeque       *fnc_deque;                                          \
     MR_EngineId         engine_id = MR_ENGINE(MR_eng_id);                    \
-    MR_IF_THREADSCOPE(                                                       \
+    MR_IF_PARPROF(                                                           \
         MR_uint_least32_t   id;                                              \
     )                                                                        \
     MR_IF_NOT_WORKSTEAL_POLLING(                                             \
@@ -836,14 +836,14 @@ do {                                                                         \
     fnc_spark.MR_spark_sync_term = (MR_SyncTerm*) &(sync_term);              \
     fnc_spark.MR_spark_resume = (child);                                     \
     fnc_spark.MR_spark_thread_local_mutables = MR_THREAD_LOCAL_MUTABLES;     \
-    MR_IF_THREADSCOPE(                                                       \
+    MR_IF_PARPROF(                                                           \
         id = MR_ENGINE(MR_eng_next_spark_id)++;                              \
         fnc_spark.MR_spark_id = (engine_id << 24)|(id & 0xFFFFFF);           \
     )                                                                        \
     fnc_deque = &MR_ENGINE(MR_eng_spark_deque);                              \
     MR_wsdeque_push_bottom(fnc_deque, &fnc_spark);                           \
-    MR_IF_THREADSCOPE(                                                       \
-        MR_threadscope_post_sparking(&(sync_term), fnc_spark.MR_spark_id);   \
+    MR_IF_PARPROF(                                                           \
+        MR_parprof_post_sparking(&(sync_term), fnc_spark.MR_spark_id);       \
     )                                                                        \
     MR_IF_NOT_WORKSTEAL_POLLING(                                             \
         action_data.MR_ewa_worksteal_engine = MR_ENGINE(MR_eng_id);          \
diff --git a/runtime/mercury_debug.c b/runtime/mercury_debug.c
index 691f529..7823631 100644
--- a/runtime/mercury_debug.c
+++ b/runtime/mercury_debug.c
@@ -1339,9 +1339,9 @@ MR_debug_log_message(const char *format, ...)
         buffer = MR_GC_realloc(buffer, len);
     }
 
-#if defined(MR_THREADSCOPE) && defined(MR_THREAD_SAFE)
-    MR_threadscope_post_log_msg(buffer);
-#elif defined(MR_THREADSCOPE)
+#if defined(MR_PARPROF) && defined(MR_THREAD_SAFE)
+    MR_parprof_post_log_msg(buffer);
+#elif defined(MR_PARPROF)
     printf("Eng %p: %s\n", MR_thread_engine_base, buffer);
 #else
     printf("%s\n", buffer);
diff --git a/runtime/mercury_debug.h b/runtime/mercury_debug.h
index ecf6fc6..f756ad0 100644
--- a/runtime/mercury_debug.h
+++ b/runtime/mercury_debug.h
@@ -263,8 +263,8 @@ extern  void    MR_print_deep_prof_var(FILE *fp, const char *name,
                     MR_CallSiteDynamic *csd);
 
 /*
-** Log a message for debugging purposes. This will log the message with
-** threadscope if available. In other parallel grades it will print the
+** Log a message for debugging purposes. This will log the message for 
+** parallel profiling if enabled. In other parallel grades it will print the
 ** address of the MercuryEngine structure with the message to stdout.
 ** In all other grades, it will print the message to standard output.
 ** There is never any need to put a newline character at the end
diff --git a/runtime/mercury_engine.c b/runtime/mercury_engine.c
index d7c0705..d40114b 100644
--- a/runtime/mercury_engine.c
+++ b/runtime/mercury_engine.c
@@ -176,9 +176,9 @@ void MR_finalize_engine(MercuryEngine *eng)
         MR_release_context(eng->MR_eng_this_context);
     }
 
-#if MR_THREADSCOPE
+#if MR_PARPROF
     if (eng->MR_eng_ts_buffer) {
-        MR_threadscope_finalize_engine(eng);
+        MR_parprof_finalize_engine(eng);
     }
 #endif
 }
@@ -531,8 +531,8 @@ MR_define_label(engine_done);
             MR_GOTO_LABEL(engine_done_2);
         }
 
-#ifdef MR_THREADSCOPE
-        MR_threadscope_post_stop_context(MR_TS_STOP_REASON_YIELDING);
+#ifdef MR_PARPROF
+        MR_parprof_post_stop_context(MR_PARPROF_STOP_REASON_YIELDING);
 #endif
         MR_save_context(this_ctxt);
         this_ctxt->MR_ctxt_resume = MR_LABEL(engine_done_2);
diff --git a/runtime/mercury_engine.h b/runtime/mercury_engine.h
index ac49580..b4ef342 100644
--- a/runtime/mercury_engine.h
+++ b/runtime/mercury_engine.h
@@ -358,9 +358,9 @@ typedef struct {
 **              to the start of the program.
 **
 ** ts_buffer
-**              The buffer object used by threadscope for this engine.
+**              The buffer object used by parallel profiling for this engine.
 **
-** id           The ID of this engine which is used by threadscope.
+** id           The ID of this engine which is used by parallel profiling.
 **
 ** next_spark_id
 **              In threadscope grades sparks are given IDs to help us track
@@ -426,14 +426,14 @@ typedef struct MR_mercury_engine_struct {
     MR_EngineId         MR_eng_id;
     MercuryThread       MR_eng_owner_thread;
     MR_Unsigned         MR_eng_c_depth;
-  #ifdef MR_THREADSCOPE
+  #ifdef MR_PARPROF
     /*
     ** For each profiling event add this offset to the time so that events on
     ** different engines that occur at the same time have the same time in
     ** clock ticks.
     */
     MR_int_least64_t                    MR_eng_cpu_clock_ticks_offset;
-    struct MR_threadscope_event_buffer  *MR_eng_ts_buffer;
+    struct MR_parprof_event_buffer      *MR_eng_ts_buffer;
     MR_uint_least32_t                   MR_eng_next_spark_id;
   #endif
   #ifdef MR_LL_PARALLEL_CONJ
diff --git a/runtime/mercury_grade.h b/runtime/mercury_grade.h
index decb081..53350b4 100644
--- a/runtime/mercury_grade.h
+++ b/runtime/mercury_grade.h
@@ -475,7 +475,7 @@
   #define MR_GRADE_OPT_PART_17  MR_GRADE_OPT_PART_16
 #endif
 
-#if defined(MR_THREADSCOPE)
+#if defined(MR_PARPROF)
   #define MR_GRADE_PART_18      MR_PASTE2(MR_GRADE_PART_17, _threadscope)
   #define MR_GRADE_OPT_PART_18  MR_GRADE_OPT_PART_17 ".threadscope"
 #else
diff --git a/runtime/mercury_memory_handlers.c b/runtime/mercury_memory_handlers.c
index 86374d0..6805011 100644
--- a/runtime/mercury_memory_handlers.c
+++ b/runtime/mercury_memory_handlers.c
@@ -1034,18 +1034,18 @@ static void
 leave_signal_handler(int sig)
 {
     fprintf(stderr, "exiting from signal handler\n");
-#if defined(MR_THREAD_SAFE) && defined(MR_THREADSCOPE)
+#if defined(MR_THREAD_SAFE) && defined(MR_PARPROF)
     if (MR_all_engine_bases) {
         int i;
         for (i = 0; i < MR_num_threads; i++) {
             if (MR_all_engine_bases[i] &&
                 MR_all_engine_bases[i]->MR_eng_ts_buffer)
             {
-                MR_threadscope_finalize_engine(MR_all_engine_bases[i]);
+                MR_parprof_finalize_engine(MR_all_engine_bases[i]);
             }
         }
     }
-    MR_finalize_threadscope();
+    MR_finalize_parprof();
 #endif
     MR_reset_signal(sig);
     raise(sig);
diff --git a/runtime/mercury_misc.h b/runtime/mercury_misc.h
index e89ae85..cd26d67 100644
--- a/runtime/mercury_misc.h
+++ b/runtime/mercury_misc.h
@@ -153,8 +153,8 @@ MR_perform_registered_exception_cleanups(void);
 #define MR_proc_exec_traces(m)                      \
     MR_PASTE2(mercury_data__proc_exec_traces_array__, m)
 
-#define MR_threadscope_strings(m)                   \
-    MR_PASTE2(mercury_data__threadscope_string_table_array__, m)
+#define MR_parprof_strings(m)                   \
+    MR_PASTE2(mercury_data__parprof_string_table_array__, m)
 
 #define MR_alloc_sites(m)                           \
     MR_PASTE2(mercury_data__alloc_sites_array__, m)
diff --git a/runtime/mercury_par_builtin.h b/runtime/mercury_par_builtin.h
index 013ee19..e06787a 100644
--- a/runtime/mercury_par_builtin.h
+++ b/runtime/mercury_par_builtin.h
@@ -93,25 +93,25 @@ vim: ft=c ts=4 sw=4 et
             Future->MR_fut_suspended = NULL;                                \
         } while (0)
 
-  #ifdef MR_THREADSCOPE
+  #ifdef MR_PARPROF
     /*
     ** In threadscope grades we need to pass the name of the future to the
-    ** threadscope event.
+    ** parallel profiling event.
     */
     #define MR_par_builtin_new_future(Future, Name)                         \
         do {                                                                \
             MR_par_builtin_new_future_2(Future);                            \
-            MR_threadscope_post_new_future(Future, Name);                   \
+            MR_parprof_post_new_future(Future, Name);                       \
         } while (0)
 
-  #else /* ! MR_THREADSCOPE */
+  #else /* ! MR_PARPROF */
 
     #define MR_par_builtin_new_future(Future)                               \
         do {                                                                \
             MR_par_builtin_new_future_2(Future);                            \
         } while (0)
 
-  #endif /* ! MR_THREADSCOPE */
+  #endif /* ! MR_PARPROF */
 
     /*
     ** If MR_fut_signalled is true, then we guarantee that reading MR_fut_value
@@ -186,8 +186,8 @@ vim: ft=c ts=4 sw=4 et
             MR_Context *next;                                               \
                                                                             \
             /*                                                              \
-            ** Post the threadscope signal future message before waking any \
-            ** threads (and posting those messages).                        \
+            ** Post the parallel profiling signal future message before     \
+            ** waking any threads (and posting those messages).             \
             */                                                              \
             MR_maybe_post_signal_future(Future);                            \
             MR_LOCK(&(Future->MR_fut_lock), "future.signal");               \
@@ -220,25 +220,25 @@ vim: ft=c ts=4 sw=4 et
             MR_UNLOCK(&(Future->MR_fut_lock), "future.signal");             \
         } while (0)
 
-#ifdef MR_THREADSCOPE
+#ifdef MR_PARPROF
     #define MR_maybe_post_stop_context                                      \
         do {                                                                \
-            MR_threadscope_post_stop_context(MR_TS_STOP_REASON_BLOCKED);    \
+            MR_parprof_post_stop_context(MR_PARPROF_STOP_REASON_BLOCKED);   \
         } while (0)
 
     #define MR_maybe_post_wait_future_nosuspend(future)                     \
         do {                                                                \
-            MR_threadscope_post_wait_future_nosuspend(future);              \
+            MR_parprof_post_wait_future_nosuspend(future);                  \
         } while (0)
 
     #define MR_maybe_post_wait_future_suspended(future)                     \
         do {                                                                \
-            MR_threadscope_post_wait_future_suspended(future);              \
+            MR_parprof_post_wait_future_suspended(future);                  \
         } while (0)
 
     #define MR_maybe_post_signal_future(future)                             \
         do {                                                                \
-            MR_threadscope_post_signal_future(future);                      \
+            MR_parprof_post_signal_future(future);                          \
         } while (0)
 
 #else
diff --git a/runtime/mercury_par_profile.c b/runtime/mercury_par_profile.c
index 789e6b0..e0be235 100644
--- a/runtime/mercury_par_profile.c
+++ b/runtime/mercury_par_profile.c
@@ -88,7 +88,7 @@
 #include <stdio.h>
 #include <string.h>
 
-#ifdef MR_THREADSCOPE
+#ifdef MR_PARPROF
 
 /***************************************************************************/
 
@@ -246,34 +246,34 @@
 #define MR_TSC_SYNC_NUM_BEST_ROUNDS (3)
 
 /* Uncomment this to enable some debugging code */
-/* #define MR_DEBUG_THREADSCOPE 1 */
+/* #define MR_DEBUG_PARPROF 1 */
 
-#if MR_DEBUG_THREADSCOPE
-#define MR_DO_THREADSCOPE_DEBUG(x) do { x; } while(0)
+#if MR_DEBUG_PARPROF
+#define MR_DO_PARPROF_DEBUG(x) do { x; } while(0)
 #else
-#define MR_DO_THREADSCOPE_DEBUG(x)
+#define MR_DO_PARPROF_DEBUG(x)
 #endif
 
 /***************************************************************************/
 
-struct MR_threadscope_event_buffer {
-    unsigned char       MR_tsbuffer_data[MR_TS_BUFFERSIZE];
+struct MR_parprof_event_buffer {
+    unsigned char       MR_ppbuffer_data[MR_TS_BUFFERSIZE];
 
     /* The current writing position in the buffer. */
-    MR_Unsigned         MR_tsbuffer_pos;
+    MR_Unsigned         MR_ppbuffer_pos;
 
     /* The position of the start of the most recent block. */
-    MR_Integer          MR_tsbuffer_block_open_pos;
+    MR_Integer          MR_ppbuffer_block_open_pos;
 
     /*
     ** True if the engine's current context is stopped, and therefore
     ** stop and start events should not be posted from the GC callback
     ** procedures.
     */
-    MR_bool             MR_tsbuffer_ctxt_is_stopped;
+    MR_bool             MR_ppbuffer_ctxt_is_stopped;
 
     /* A cheap userspace lock to make buffers reentrant. */
-    volatile MR_Us_Lock MR_tsbuffer_lock;
+    volatile MR_Us_Lock MR_ppbuffer_lock;
 };
 
 /*
@@ -665,12 +665,12 @@ static EventTypeDesc event_type_descs[] = {
 static MR_int_least16_t event_type_sizes[MR_TS_NUM_EVENT_TAGS];
 static MR_int_least16_t event_type_sizes_mercury[MR_TS_NUM_MER_EVENTS];
 
-static FILE* MR_threadscope_output_file = NULL;
-static char* MR_threadscope_output_filename;
+static FILE* MR_parprof_output_file = NULL;
+static char* MR_parprof_output_filename;
 
 /*
 ** The TSC value recorded when the primordial thread called
-** MR_setup_threadscope(), this is used retroactivly to initialise the
+** MR_setup_parprof(), this is used retroactivly to initialise the
 ** MR_eng_cpu_clock_ticks_offset field in the engine structure once it is
 ** created.
 */
@@ -678,21 +678,21 @@ static MR_uint_least64_t MR_primordial_first_tsc;
 
 static Timedelta        MR_global_offset;
 
-static struct MR_threadscope_event_buffer global_buffer;
+static struct MR_parprof_event_buffer global_buffer;
 
 /*
 ** Alternativly we use gettimeofday for measuring time.
 */
-MR_bool                 MR_threadscope_use_tsc = MR_FALSE;
+MR_bool                 MR_parprof_use_tsc = MR_FALSE;
 static Timedelta        MR_gettimeofday_offset;
 
 /*
 ** An ID that may be allocated to the next string to be registered.
 */
-static MR_TS_StringId   MR_next_string_id = 0;
-static MR_EngSetId      next_engset_id = 0;
+static MR_Parprof_StringId  MR_next_string_id = 0;
+static MR_EngSetId          next_engset_id = 0;
 
-static MR_EngSetId      process_engset_id;
+static MR_EngSetId          process_engset_id;
 
 /***************************************************************************/
 
@@ -730,11 +730,11 @@ event_type_size(EventType event_type) {
 ** for this statically sized event _and_ for the block marker event.
 */
 MR_STATIC_INLINE MR_bool
-enough_room_for_event(struct MR_threadscope_event_buffer *buffer,
+enough_room_for_event(struct MR_parprof_event_buffer *buffer,
     EventType event_type)
 {
     int needed =
-        buffer->MR_tsbuffer_pos +
+        buffer->MR_ppbuffer_pos +
         event_type_size(event_type) +
         event_type_size(MR_TS_EVENT_BLOCK_MARKER) +
         ((2 + 8) * 2); /* (EventType, Time) * 2 */
@@ -742,11 +742,11 @@ enough_room_for_event(struct MR_threadscope_event_buffer *buffer,
 }
 
 MR_STATIC_INLINE MR_bool
-enough_room_for_variable_size_event(struct MR_threadscope_event_buffer *buffer,
+enough_room_for_variable_size_event(struct MR_parprof_event_buffer *buffer,
     MR_Unsigned length)
 {
     int needed =
-        buffer->MR_tsbuffer_pos +
+        buffer->MR_ppbuffer_pos +
         length +
         event_type_size(MR_TS_EVENT_BLOCK_MARKER) +
         ((2 + 8) * 2); /* (EventType, Time) * 2 */
@@ -757,42 +757,42 @@ enough_room_for_variable_size_event(struct MR_threadscope_event_buffer *buffer,
 ** Is a block currently open?
 */
 MR_STATIC_INLINE MR_bool block_is_open(
-    struct MR_threadscope_event_buffer *buffer)
+    struct MR_parprof_event_buffer *buffer)
 {
-    return !(buffer->MR_tsbuffer_block_open_pos == -1);
+    return !(buffer->MR_ppbuffer_block_open_pos == -1);
 }
 
 /*
 ** Put words into the current engine's buffer in big endian order.
 */
-MR_STATIC_INLINE void put_byte(struct MR_threadscope_event_buffer *buffer,
+MR_STATIC_INLINE void put_byte(struct MR_parprof_event_buffer *buffer,
     int byte)
 {
-    buffer->MR_tsbuffer_data[buffer->MR_tsbuffer_pos++] = byte;
+    buffer->MR_ppbuffer_data[buffer->MR_ppbuffer_pos++] = byte;
 }
 
-MR_STATIC_INLINE void put_be_int16(struct MR_threadscope_event_buffer *buffer,
+MR_STATIC_INLINE void put_be_int16(struct MR_parprof_event_buffer *buffer,
     MR_int_least16_t word)
 {
     put_byte(buffer, (word >> 8) & 0xFF);
     put_byte(buffer, word & 0xFF);
 }
 
-MR_STATIC_INLINE void put_be_uint16(struct MR_threadscope_event_buffer *buffer,
+MR_STATIC_INLINE void put_be_uint16(struct MR_parprof_event_buffer *buffer,
     MR_uint_least16_t word)
 {
     put_byte(buffer, (word >> 8) & 0xFF);
     put_byte(buffer, word & 0xFF);
 }
 
-MR_STATIC_INLINE void put_be_uint32(struct MR_threadscope_event_buffer *buffer,
+MR_STATIC_INLINE void put_be_uint32(struct MR_parprof_event_buffer *buffer,
     MR_uint_least32_t word)
 {
     put_be_uint16(buffer, (word >> 16) & 0xFFFF);
     put_be_uint16(buffer, word & 0xFFFF);
 }
 
-MR_STATIC_INLINE void put_be_uint64(struct MR_threadscope_event_buffer *buffer,
+MR_STATIC_INLINE void put_be_uint64(struct MR_parprof_event_buffer *buffer,
     MR_uint_least64_t word)
 {
     put_be_uint32(buffer, (word >> 32) & 0xFFFFFFFF);
@@ -800,7 +800,7 @@ MR_STATIC_INLINE void put_be_uint64(struct MR_threadscope_event_buffer *buffer,
 }
 
 MR_STATIC_INLINE void put_raw_string(
-    struct MR_threadscope_event_buffer *buffer,
+    struct MR_parprof_event_buffer *buffer,
     const char *string, unsigned len)
 {
     unsigned i;
@@ -814,7 +814,7 @@ MR_STATIC_INLINE void put_raw_string(
 ** by a 16 bit integer giving the string's length.
 */
 MR_STATIC_INLINE void put_string_size16(
-    struct MR_threadscope_event_buffer *buffer, const char *string)
+    struct MR_parprof_event_buffer *buffer, const char *string)
 {
     unsigned i, len;
 
@@ -828,7 +828,7 @@ MR_STATIC_INLINE void put_string_size16(
 ** by a 32 bit integer giving the string's length.
 */
 MR_STATIC_INLINE void put_string_size32(
-    struct MR_threadscope_event_buffer *buffer, const char *string)
+    struct MR_parprof_event_buffer *buffer, const char *string)
 {
     unsigned i, len;
 
@@ -837,75 +837,75 @@ MR_STATIC_INLINE void put_string_size32(
     put_raw_string(buffer, string, len);
 }
 
-MR_STATIC_INLINE void put_timestamp(struct MR_threadscope_event_buffer *buffer,
+MR_STATIC_INLINE void put_timestamp(struct MR_parprof_event_buffer *buffer,
     Time timestamp)
 {
     put_be_uint64(buffer, timestamp);
 }
 
 MR_STATIC_INLINE void put_eventlog_offset(
-    struct MR_threadscope_event_buffer *buffer, EventlogOffset offset)
+    struct MR_parprof_event_buffer *buffer, EventlogOffset offset)
 {
     put_be_uint32(buffer, offset);
 }
 
 MR_STATIC_INLINE void put_event_header(
-    struct MR_threadscope_event_buffer *buffer,
+    struct MR_parprof_event_buffer *buffer,
     EventType event_type, Time timestamp)
 {
     put_be_uint16(buffer, event_type);
     put_timestamp(buffer, timestamp);
 }
 
-MR_STATIC_INLINE void put_engine_id(struct MR_threadscope_event_buffer *buffer,
+MR_STATIC_INLINE void put_engine_id(struct MR_parprof_event_buffer *buffer,
     MR_EngineId engine_num)
 {
     put_be_uint16(buffer, engine_num);
 }
 
 MR_STATIC_INLINE void put_context_id(
-    struct MR_threadscope_event_buffer *buffer, MR_ContextId context_id)
+    struct MR_parprof_event_buffer *buffer, MR_ContextId context_id)
 {
     put_be_uint32(buffer, context_id);
 }
 
 MR_STATIC_INLINE void put_stop_reason(
-    struct MR_threadscope_event_buffer *buffer, MR_ContextStopReason reason)
+    struct MR_parprof_event_buffer *buffer, MR_ContextStopReason reason)
 {
     put_be_uint16(buffer, reason);
 }
 
-MR_STATIC_INLINE void put_string_id(struct MR_threadscope_event_buffer *buffer,
-    MR_TS_StringId id)
+MR_STATIC_INLINE void put_string_id(struct MR_parprof_event_buffer *buffer,
+    MR_Parprof_StringId id)
 {
     put_be_uint32(buffer, id);
 }
 
 MR_STATIC_INLINE void put_par_conj_dynamic_id(
-    struct MR_threadscope_event_buffer *buffer, MR_Word* id)
+    struct MR_parprof_event_buffer *buffer, MR_Word* id)
 {
     put_be_uint64(buffer, (MR_Word)id);
 }
 
-MR_STATIC_INLINE void put_spark_id(struct MR_threadscope_event_buffer *buffer,
+MR_STATIC_INLINE void put_spark_id(struct MR_parprof_event_buffer *buffer,
     MR_SparkId spark_id)
 {
     put_be_uint32(buffer, spark_id);
 }
 
-MR_STATIC_INLINE void put_engset_id(struct MR_threadscope_event_buffer *buffer,
+MR_STATIC_INLINE void put_engset_id(struct MR_parprof_event_buffer *buffer,
     MR_EngSetId engset_id)
 {
     put_be_uint32(buffer, engset_id);
 }
 
 MR_STATIC_INLINE void put_engset_type(
-    struct MR_threadscope_event_buffer *buffer, MR_EngSetType type)
+    struct MR_parprof_event_buffer *buffer, MR_EngSetType type)
 {
     put_be_uint16(buffer, type);
 }
 
-MR_STATIC_INLINE void put_future_id(struct MR_threadscope_event_buffer *buffer,
+MR_STATIC_INLINE void put_future_id(struct MR_parprof_event_buffer *buffer,
     MR_Future* id)
 {
     put_be_uint64(buffer, (MR_Word)id);
@@ -913,7 +913,7 @@ MR_STATIC_INLINE void put_future_id(struct MR_threadscope_event_buffer *buffer,
 
 /***************************************************************************/
 
-static struct MR_threadscope_event_buffer* MR_create_event_buffer(void);
+static struct MR_parprof_event_buffer* MR_create_event_buffer(void);
 
 /*
 ** The prelude is everything up to and including the 'DATA_BEGIN' marker.
@@ -922,20 +922,20 @@ static void MR_open_output_file_and_write_prelude(void);
 
 static void MR_close_output_file(void);
 
-static void put_event_type(struct MR_threadscope_event_buffer *buffer,
+static void put_event_type(struct MR_parprof_event_buffer *buffer,
                 EventTypeDesc *event_type);
 
-static MR_bool flush_event_buffer(struct MR_threadscope_event_buffer *buffer);
+static MR_bool flush_event_buffer(struct MR_parprof_event_buffer *buffer);
 
-static void maybe_close_block(struct MR_threadscope_event_buffer *buffer);
+static void maybe_close_block(struct MR_parprof_event_buffer *buffer);
 
-static void open_block(struct MR_threadscope_event_buffer *buffer,
+static void open_block(struct MR_parprof_event_buffer *buffer,
                 MR_Unsigned eng_id);
 
 /***************************************************************************/
 
-static MR_TS_StringId
-MR_threadscope_register_string(const char *string);
+static MR_Parprof_StringId
+MR_parprof_register_string(const char *string);
 
 /*
 ** These four events are used to create and manage engine sets.
@@ -943,16 +943,16 @@ MR_threadscope_register_string(const char *string);
 **
 ** The first two work on the global event buffer and are not thread safe.
 */
-static void MR_threadscope_post_create_engset(MR_EngSetId id,
+static void MR_parprof_post_create_engset(MR_EngSetId id,
                 MR_EngSetType type);
 
-static void MR_threadscope_post_destroy_engset(MR_EngSetId id);
+static void MR_parprof_post_destroy_engset(MR_EngSetId id);
 
-static void MR_threadscope_post_engset_add(
-                struct MR_threadscope_event_buffer *buffer,
+static void MR_parprof_post_engset_add(
+                struct MR_parprof_event_buffer *buffer,
                 MR_EngSetId id, MR_EngineId eng);
 
-static void MR_threadscope_post_engset_remove(MR_EngSetId id, MR_EngineId eng);
+static void MR_parprof_post_engset_remove(MR_EngSetId id, MR_EngineId eng);
 
 /*
 ** Post the name and version of the runtime system to the log file.
@@ -962,7 +962,7 @@ static void MR_threadscope_post_engset_remove(MR_EngSetId id, MR_EngineId eng);
 **
 ** The name and version are separated by a '-'.
 */
-static void MR_threadscope_post_runtime_identifier(MR_EngSetId id,
+static void MR_parprof_post_runtime_identifier(MR_EngSetId id,
                 const char *ident);
 
 /***************************************************************************/
@@ -980,17 +980,18 @@ static Time gettimeofday_nsecs(void);
 /***************************************************************************/
 
 void
-MR_setup_threadscope(void)
+MR_setup_parprof(void)
 {
-    MR_DO_THREADSCOPE_DEBUG(
-        fprintf(stderr, "In setup threadscope thread: 0x%lx\n", pthread_self())
+    MR_DO_PARPROF_DEBUG(
+        fprintf(stderr, "In setup parallel profiling for thread: 0x%lx\n",
+            pthread_self())
     );
 
     if (!MR_tsc_is_sensible()) {
-        MR_threadscope_use_tsc = MR_FALSE;
+        MR_parprof_use_tsc = MR_FALSE;
     }
 
-    if (MR_threadscope_use_tsc) {
+    if (MR_parprof_use_tsc) {
         /* This value is used later when setting up the primordial engine. */
         MR_primordial_first_tsc = MR_read_cpu_tsc();
 
@@ -1018,18 +1019,18 @@ MR_setup_threadscope(void)
 #endif
 
     /* Clear the global buffer and setup the file */
-    global_buffer.MR_tsbuffer_pos = 0;
-    global_buffer.MR_tsbuffer_block_open_pos = -1;
-    global_buffer.MR_tsbuffer_lock = MR_US_LOCK_INITIAL_VALUE;
+    global_buffer.MR_ppbuffer_pos = 0;
+    global_buffer.MR_ppbuffer_block_open_pos = -1;
+    global_buffer.MR_ppbuffer_lock = MR_US_LOCK_INITIAL_VALUE;
     MR_open_output_file_and_write_prelude();
 
     /*
     ** Post the initial events to the buffer.
     */
     process_engset_id = get_next_engset_id();
-    MR_threadscope_post_create_engset(process_engset_id,
+    MR_parprof_post_create_engset(process_engset_id,
         MR_TS_ENGSET_TYPE_OSPROCESS);
-    MR_threadscope_post_runtime_identifier(process_engset_id,
+    MR_parprof_post_runtime_identifier(process_engset_id,
         "mmc-" MR_VERSION);
 
     /*
@@ -1042,29 +1043,30 @@ MR_setup_threadscope(void)
 }
 
 void
-MR_finalize_threadscope(void)
+MR_finalize_parprof(void)
 {
-    MR_DO_THREADSCOPE_DEBUG(
-        fprintf(stderr, "In finalize threadscope thread: 0x%lx\n",
+    MR_DO_PARPROF_DEBUG(
+        fprintf(stderr, "In finalize parallel profiling for thread: 0x%lx\n",
             pthread_self())
     );
 
-    MR_threadscope_post_destroy_engset(process_engset_id);
+    MR_parprof_post_destroy_engset(process_engset_id);
 
     flush_event_buffer(&global_buffer);
     MR_close_output_file();
 }
 
 void
-MR_threadscope_setup_engine(MercuryEngine *eng)
+MR_parprof_setup_engine(MercuryEngine *eng)
 {
-    MR_DO_THREADSCOPE_DEBUG(
-        fprintf(stderr, "In threadscope setup engine thread: 0x%lx\n",
+    MR_DO_PARPROF_DEBUG(
+        fprintf(stderr,
+            "In parallel profiling setup for engine thread: 0x%lx\n",
             pthread_self())
     );
     eng->MR_eng_next_spark_id = 0;
 
-    if (MR_threadscope_use_tsc) {
+    if (MR_parprof_use_tsc) {
         if (eng->MR_eng_id == 0) {
             MR_global_offset = -MR_primordial_first_tsc;
         }
@@ -1073,7 +1075,7 @@ MR_threadscope_setup_engine(MercuryEngine *eng)
 
     eng->MR_eng_ts_buffer = MR_create_event_buffer();
 
-    MR_threadscope_post_engset_add(eng->MR_eng_ts_buffer, process_engset_id,
+    MR_parprof_post_engset_add(eng->MR_eng_ts_buffer, process_engset_id,
         eng->MR_eng_id);
     /*
     ** Flush the buffer to ensure the message above (which lacks a timestamp)
@@ -1083,18 +1085,19 @@ MR_threadscope_setup_engine(MercuryEngine *eng)
 }
 
 void
-MR_threadscope_finalize_engine(MercuryEngine *eng)
+MR_parprof_finalize_engine(MercuryEngine *eng)
 {
-    struct MR_threadscope_event_buffer *buffer = eng->MR_eng_ts_buffer;
+    struct MR_parprof_event_buffer *buffer = eng->MR_eng_ts_buffer;
 
-    MR_DO_THREADSCOPE_DEBUG(
-        fprintf(stderr, "In threadscope finalize engine thread: 0x%lx\n",
+    MR_DO_PARPROF_DEBUG(
+        fprintf(stderr,
+            "In parallel profiling finalize for engine thread: 0x%lx\n",
             pthread_self())
     );
 
-    MR_threadscope_post_engset_remove(process_engset_id, eng->MR_eng_id);
+    MR_parprof_post_engset_remove(process_engset_id, eng->MR_eng_id);
 
-    MR_US_SPIN_LOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_SPIN_LOCK(&(buffer->MR_ppbuffer_lock));
 
     if (!enough_room_for_event(buffer, MR_TS_EVENT_SHUTDOWN)) {
         flush_event_buffer(buffer);
@@ -1106,7 +1109,7 @@ MR_threadscope_finalize_engine(MercuryEngine *eng)
 
     flush_event_buffer(buffer);
     eng->MR_eng_ts_buffer = NULL;
-    MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
 }
 
 #if 0
@@ -1143,7 +1146,7 @@ static Time                 MR_tsc_sync_master_time;
 static int compare_time_delay_offset_by_delay(const void *a, const void *b);
 
 void
-MR_threadscope_sync_tsc_master(void)
+MR_parprof_sync_tsc_master(void)
 {
     unsigned i;
 
@@ -1165,7 +1168,7 @@ MR_threadscope_sync_tsc_master(void)
 }
 
 void
-MR_threadscope_sync_tsc_slave(void)
+MR_parprof_sync_tsc_slave(void)
 {
     unsigned        i, j;
     TimeDelayOffset delay_offset[MR_TSC_SYNC_NUM_ROUNDS];
@@ -1173,7 +1176,7 @@ MR_threadscope_sync_tsc_slave(void)
     MercuryEngine   *eng = MR_thread_engine_base;
 
     /* Only one slave may enter at a time. */
-    MR_LOCK(&MR_tsc_sync_slave_lock, "MR_threadscope_sync_tsc_slave");
+    MR_LOCK(&MR_tsc_sync_slave_lock, "MR_parprof_sync_tsc_slave");
 
     /*
     ** Tell the master we are ready to begin, and wait for it to tell us
@@ -1222,7 +1225,7 @@ MR_threadscope_sync_tsc_slave(void)
     ** We do this debugging output while holding the lock, so that the output
     ** is reasonable.
     */
-    MR_DO_THREADSCOPE_DEBUG({
+    MR_DO_PARPROF_DEBUG({
         fprintf(stderr, "TSC Synchronization for thread 0x%x\n",
             pthread_self());
         for (i = 0; i < MR_TSC_SYNC_NUM_ROUNDS; i++) {
@@ -1232,7 +1235,7 @@ MR_threadscope_sync_tsc_slave(void)
                 delay_offset[i].offset + MR_global_offset);
         }
     });
-    MR_UNLOCK(&MR_tsc_sync_slave_lock, "MR_threadscope_sync_tsc_slave");
+    MR_UNLOCK(&MR_tsc_sync_slave_lock, "MR_parprof_sync_tsc_slave");
 
     /* Now to average the best offsets. */
     qsort(&delay_offset, MR_TSC_SYNC_NUM_ROUNDS, sizeof(TimeDelayOffset),
@@ -1243,7 +1246,7 @@ MR_threadscope_sync_tsc_slave(void)
     }
     eng->MR_eng_cpu_clock_ticks_offset = total_offset + MR_global_offset;
 
-    MR_DO_THREADSCOPE_DEBUG({
+    MR_DO_PARPROF_DEBUG({
         fprintf(stderr, "TSC Synchronization offset for thread 0x%x: %ld\n",
             pthread_self(), eng->MR_eng_cpu_clock_ticks_offset);
     });
@@ -1268,11 +1271,11 @@ compare_time_delay_offset_by_delay(const void *a, const void *b) {
 /***************************************************************************/
 
 void
-MR_threadscope_post_create_context(MR_Context *context)
+MR_parprof_post_create_context(MR_Context *context)
 {
-    struct MR_threadscope_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
+    struct MR_parprof_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
 
-    MR_US_SPIN_LOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_SPIN_LOCK(&(buffer->MR_ppbuffer_lock));
 
     if (!enough_room_for_event(buffer, MR_TS_EVENT_CREATE_THREAD)) {
         flush_event_buffer(buffer);
@@ -1285,15 +1288,15 @@ MR_threadscope_post_create_context(MR_Context *context)
         get_current_time_nanosecs());
     put_context_id(buffer, context->MR_ctxt_num_id);
 
-    MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
 }
 
 void
-MR_threadscope_post_reuse_context(MR_Context *context, MR_Unsigned old_id)
+MR_parprof_post_reuse_context(MR_Context *context, MR_Unsigned old_id)
 {
-    struct MR_threadscope_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
+    struct MR_parprof_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
 
-    MR_US_SPIN_LOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_SPIN_LOCK(&(buffer->MR_ppbuffer_lock));
 
     if (!enough_room_for_event(buffer, MR_TS_MER_EVENT_REUSE_THREAD)) {
         flush_event_buffer(buffer);
@@ -1307,15 +1310,15 @@ MR_threadscope_post_reuse_context(MR_Context *context, MR_Unsigned old_id)
     put_context_id(buffer, context->MR_ctxt_num_id);
     put_context_id(buffer, old_id);
 
-    MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
 }
 
 void
-MR_threadscope_post_create_context_for_spark(MR_Context *context)
+MR_parprof_post_create_context_for_spark(MR_Context *context)
 {
-    struct MR_threadscope_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
+    struct MR_parprof_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
 
-    MR_US_SPIN_LOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_SPIN_LOCK(&(buffer->MR_ppbuffer_lock));
 
     if (!enough_room_for_event(buffer, MR_TS_EVENT_CREATE_SPARK_THREAD)) {
         flush_event_buffer(buffer);
@@ -1328,15 +1331,15 @@ MR_threadscope_post_create_context_for_spark(MR_Context *context)
         get_current_time_nanosecs());
     put_context_id(buffer, context->MR_ctxt_num_id);
 
-    MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
 }
 
 void
-MR_threadscope_post_release_context(MR_Context *context)
+MR_parprof_post_release_context(MR_Context *context)
 {
-    struct MR_threadscope_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
+    struct MR_parprof_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
 
-    MR_US_SPIN_LOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_SPIN_LOCK(&(buffer->MR_ppbuffer_lock));
 
     if (!enough_room_for_event(buffer, MR_TS_MER_EVENT_RELEASE_CONTEXT)) {
         flush_event_buffer(buffer);
@@ -1349,15 +1352,15 @@ MR_threadscope_post_release_context(MR_Context *context)
         get_current_time_nanosecs());
     put_context_id(buffer, context->MR_ctxt_num_id);
 
-    MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
 }
 
 void
-MR_threadscope_post_context_runnable(MR_Context *context)
+MR_parprof_post_context_runnable(MR_Context *context)
 {
-    struct MR_threadscope_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
+    struct MR_parprof_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
 
-    MR_US_SPIN_LOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_SPIN_LOCK(&(buffer->MR_ppbuffer_lock));
 
     if (!enough_room_for_event(buffer, MR_TS_EVENT_THREAD_RUNNABLE)) {
         flush_event_buffer(buffer);
@@ -1370,12 +1373,12 @@ MR_threadscope_post_context_runnable(MR_Context *context)
         get_current_time_nanosecs());
     put_context_id(buffer, context->MR_ctxt_num_id);
 
-    MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
 }
 
 static void
-MR_threadscope_post_run_context_locked(
-    struct MR_threadscope_event_buffer *buffer, MR_Context *context)
+MR_parprof_post_run_context_locked(
+    struct MR_parprof_event_buffer *buffer, MR_Context *context)
 {
     if (!enough_room_for_event(buffer, MR_TS_EVENT_RUN_THREAD)) {
         flush_event_buffer(buffer);
@@ -1391,9 +1394,9 @@ MR_threadscope_post_run_context_locked(
 }
 
 void
-MR_threadscope_post_run_context(void)
+MR_parprof_post_run_context(void)
 {
-    struct MR_threadscope_event_buffer  *buffer;
+    struct MR_parprof_event_buffer  *buffer;
     MR_Context                          *context;
 
     buffer = MR_thread_engine_base->MR_eng_ts_buffer;
@@ -1401,18 +1404,18 @@ MR_threadscope_post_run_context(void)
     context = MR_thread_engine_base->MR_eng_this_context;
 
     if (context) {
-        MR_US_SPIN_LOCK(&(buffer->MR_tsbuffer_lock));
-        if (buffer->MR_tsbuffer_ctxt_is_stopped) {
-            MR_threadscope_post_run_context_locked(buffer, context);
-            buffer->MR_tsbuffer_ctxt_is_stopped = MR_FALSE;
+        MR_US_SPIN_LOCK(&(buffer->MR_ppbuffer_lock));
+        if (buffer->MR_ppbuffer_ctxt_is_stopped) {
+            MR_parprof_post_run_context_locked(buffer, context);
+            buffer->MR_ppbuffer_ctxt_is_stopped = MR_FALSE;
         }
-        MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+        MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
     }
 }
 
 static void
-MR_threadscope_post_stop_context_locked(
-    struct MR_threadscope_event_buffer *buffer,
+MR_parprof_post_stop_context_locked(
+    struct MR_parprof_event_buffer *buffer,
     MR_Context *context, MR_ContextStopReason reason)
 {
     if (!enough_room_for_event(buffer, MR_TS_EVENT_STOP_THREAD)) {
@@ -1429,30 +1432,30 @@ MR_threadscope_post_stop_context_locked(
 }
 
 void
-MR_threadscope_post_stop_context(MR_ContextStopReason reason)
+MR_parprof_post_stop_context(MR_ContextStopReason reason)
 {
-    struct MR_threadscope_event_buffer  *buffer;
+    struct MR_parprof_event_buffer  *buffer;
     MR_Context                          *context;
 
     buffer = MR_thread_engine_base->MR_eng_ts_buffer;
     context = MR_thread_engine_base->MR_eng_this_context;
 
-    MR_US_SPIN_LOCK(&(buffer->MR_tsbuffer_lock));
-    if (!buffer->MR_tsbuffer_ctxt_is_stopped) {
-        MR_threadscope_post_stop_context_locked(buffer, context, reason);
-        buffer->MR_tsbuffer_ctxt_is_stopped = MR_TRUE;
+    MR_US_SPIN_LOCK(&(buffer->MR_ppbuffer_lock));
+    if (!buffer->MR_ppbuffer_ctxt_is_stopped) {
+        MR_parprof_post_stop_context_locked(buffer, context, reason);
+        buffer->MR_ppbuffer_ctxt_is_stopped = MR_TRUE;
     }
-    MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
 }
 
 void
-MR_threadscope_post_run_spark(MR_SparkId spark_id)
+MR_parprof_post_run_spark(MR_SparkId spark_id)
 {
-    struct MR_threadscope_event_buffer  *buffer;
+    struct MR_parprof_event_buffer  *buffer;
 
     buffer = MR_thread_engine_base->MR_eng_ts_buffer;
 
-    MR_US_SPIN_LOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_SPIN_LOCK(&(buffer->MR_ppbuffer_lock));
     if (!enough_room_for_event(buffer, MR_TS_MER_EVENT_SPARK_RUN)) {
         flush_event_buffer(buffer);
         open_block(buffer, MR_ENGINE(MR_eng_id));
@@ -1463,18 +1466,18 @@ MR_threadscope_post_run_spark(MR_SparkId spark_id)
     put_event_header(buffer, MR_TS_MER_EVENT_SPARK_RUN,
         get_current_time_nanosecs());
     put_spark_id(buffer, spark_id);
-    MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
 }
 
 void
-MR_threadscope_post_steal_spark(MR_SparkId spark_id)
+MR_parprof_post_steal_spark(MR_SparkId spark_id)
 {
-    struct MR_threadscope_event_buffer  *buffer;
+    struct MR_parprof_event_buffer  *buffer;
     unsigned                            engine_id;
 
     buffer = MR_thread_engine_base->MR_eng_ts_buffer;
 
-    MR_US_SPIN_LOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_SPIN_LOCK(&(buffer->MR_ppbuffer_lock));
     if (!enough_room_for_event(buffer, MR_TS_MER_EVENT_SPARK_STEAL)) {
         flush_event_buffer(buffer);
         open_block(buffer, MR_ENGINE(MR_eng_id));
@@ -1493,15 +1496,15 @@ MR_threadscope_post_steal_spark(MR_SparkId spark_id)
     engine_id = (spark_id & 0xFF000000) >> 24;
     put_be_uint16(buffer, engine_id);
     put_spark_id(buffer, spark_id);
-    MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
 }
 
 void
-MR_threadscope_post_sparking(MR_Word* dynamic_conj_id, MR_SparkId spark_id)
+MR_parprof_post_sparking(MR_Word* dynamic_conj_id, MR_SparkId spark_id)
 {
-    struct MR_threadscope_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
+    struct MR_parprof_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
 
-    MR_US_SPIN_LOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_SPIN_LOCK(&(buffer->MR_ppbuffer_lock));
     if (!enough_room_for_event(buffer, MR_TS_MER_EVENT_SPARK_CREATE)) {
         flush_event_buffer(buffer);
         open_block(buffer, MR_ENGINE(MR_eng_id));
@@ -1514,15 +1517,15 @@ MR_threadscope_post_sparking(MR_Word* dynamic_conj_id, MR_SparkId spark_id)
     put_par_conj_dynamic_id(buffer, dynamic_conj_id);
     put_spark_id(buffer, spark_id);
 
-    MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
 }
 
 void
-MR_threadscope_post_calling_main(void)
+MR_parprof_post_calling_main(void)
 {
-    struct MR_threadscope_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
+    struct MR_parprof_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
 
-    MR_US_SPIN_LOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_SPIN_LOCK(&(buffer->MR_ppbuffer_lock));
     if (!enough_room_for_event(buffer, MR_TS_MER_EVENT_CALLING_MAIN)) {
         flush_event_buffer(buffer);
         open_block(buffer, MR_ENGINE(MR_eng_id));
@@ -1532,15 +1535,15 @@ MR_threadscope_post_calling_main(void)
 
     put_event_header(buffer, MR_TS_MER_EVENT_CALLING_MAIN,
         get_current_time_nanosecs());
-    MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
 }
 
 void
-MR_threadscope_post_looking_for_global_context(void)
+MR_parprof_post_looking_for_global_context(void)
 {
-    struct MR_threadscope_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
+    struct MR_parprof_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
 
-    MR_US_SPIN_LOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_SPIN_LOCK(&(buffer->MR_ppbuffer_lock));
     if (!enough_room_for_event(buffer,
             MR_TS_MER_EVENT_LOOKING_FOR_GLOBAL_CONTEXT))
     {
@@ -1552,15 +1555,15 @@ MR_threadscope_post_looking_for_global_context(void)
 
     put_event_header(buffer, MR_TS_MER_EVENT_LOOKING_FOR_GLOBAL_CONTEXT,
         get_current_time_nanosecs());
-    MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
 }
 
 void
-MR_threadscope_post_looking_for_local_spark(void)
+MR_parprof_post_looking_for_local_spark(void)
 {
-    struct MR_threadscope_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
+    struct MR_parprof_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
 
-    MR_US_SPIN_LOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_SPIN_LOCK(&(buffer->MR_ppbuffer_lock));
     if (!enough_room_for_event(buffer, MR_TS_MER_EVENT_LOOKING_FOR_LOCAL_SPARK)) {
         flush_event_buffer(buffer);
         open_block(buffer, MR_ENGINE(MR_eng_id));
@@ -1570,15 +1573,15 @@ MR_threadscope_post_looking_for_local_spark(void)
 
     put_event_header(buffer, MR_TS_MER_EVENT_LOOKING_FOR_LOCAL_SPARK,
         get_current_time_nanosecs());
-    MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
 }
 
 void
-MR_threadscope_post_work_stealing(void)
+MR_parprof_post_work_stealing(void)
 {
-    struct MR_threadscope_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
+    struct MR_parprof_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
 
-    MR_US_SPIN_LOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_SPIN_LOCK(&(buffer->MR_ppbuffer_lock));
     if (!enough_room_for_event(buffer, MR_TS_MER_EVENT_WORK_STEALING)) {
         flush_event_buffer(buffer);
         open_block(buffer, MR_ENGINE(MR_eng_id));
@@ -1588,16 +1591,16 @@ MR_threadscope_post_work_stealing(void)
 
     put_event_header(buffer, MR_TS_MER_EVENT_WORK_STEALING,
         get_current_time_nanosecs());
-    MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
 }
 
 void
-MR_threadscope_post_start_par_conj(MR_Word* dynamic_id,
-    MR_TS_StringId static_id)
+MR_parprof_post_start_par_conj(MR_Word* dynamic_id,
+    MR_Parprof_StringId static_id)
 {
-    struct MR_threadscope_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
+    struct MR_parprof_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
 
-    MR_US_SPIN_LOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_SPIN_LOCK(&(buffer->MR_ppbuffer_lock));
     if (!enough_room_for_event(buffer, MR_TS_MER_EVENT_START_PAR_CONJ)) {
         flush_event_buffer(buffer);
         open_block(buffer, MR_ENGINE(MR_eng_id));
@@ -1610,15 +1613,15 @@ MR_threadscope_post_start_par_conj(MR_Word* dynamic_id,
     put_par_conj_dynamic_id(buffer, dynamic_id);
     put_string_id(buffer, static_id);
 
-    MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
 }
 
 void
-MR_threadscope_post_end_par_conj(MR_Word *dynamic_id)
+MR_parprof_post_end_par_conj(MR_Word *dynamic_id)
 {
-    struct MR_threadscope_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
+    struct MR_parprof_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
 
-    MR_US_SPIN_LOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_SPIN_LOCK(&(buffer->MR_ppbuffer_lock));
     if (!enough_room_for_event(buffer, MR_TS_MER_EVENT_END_PAR_CONJ)) {
         flush_event_buffer(buffer);
         open_block(buffer, MR_ENGINE(MR_eng_id));
@@ -1630,15 +1633,15 @@ MR_threadscope_post_end_par_conj(MR_Word *dynamic_id)
         get_current_time_nanosecs());
     put_par_conj_dynamic_id(buffer, dynamic_id);
 
-    MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
 }
 
 void
-MR_threadscope_post_end_par_conjunct(MR_Word *dynamic_id)
+MR_parprof_post_end_par_conjunct(MR_Word *dynamic_id)
 {
-    struct MR_threadscope_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
+    struct MR_parprof_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
 
-    MR_US_SPIN_LOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_SPIN_LOCK(&(buffer->MR_ppbuffer_lock));
     if (!enough_room_for_event(buffer, MR_TS_MER_EVENT_END_PAR_CONJUNCT)) {
         flush_event_buffer(buffer);
         open_block(buffer, MR_ENGINE(MR_eng_id));
@@ -1650,16 +1653,16 @@ MR_threadscope_post_end_par_conjunct(MR_Word *dynamic_id)
         get_current_time_nanosecs());
     put_par_conj_dynamic_id(buffer, dynamic_id);
 
-    MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
 }
 
 /*
 ** Register a string for use in future messages.
 */
-static MR_TS_StringId
-MR_threadscope_register_string(const char *string)
+static MR_Parprof_StringId
+MR_parprof_register_string(const char *string)
 {
-    MR_TS_StringId id;
+    MR_Parprof_StringId id;
     unsigned length;
 
     length = strlen(string);
@@ -1684,25 +1687,25 @@ MR_threadscope_register_string(const char *string)
 }
 
 void
-MR_threadscope_register_strings_array(MR_Threadscope_String *array,
+MR_parprof_register_strings_array(MR_Parprof_String *array,
     unsigned size)
 {
     unsigned i;
 
     for (i = 0; i < size; i++) {
-        array[i].MR_tsstring_id =
-            MR_threadscope_register_string(array[i].MR_tsstring_string);
+        array[i].MR_ppstring_id =
+            MR_parprof_register_string(array[i].MR_ppstring_string);
     }
 
     flush_event_buffer(&global_buffer);
 }
 
 void
-MR_threadscope_post_log_msg(const char *message)
+MR_parprof_post_log_msg(const char *message)
 {
-    struct MR_threadscope_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
+    struct MR_parprof_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
 
-    MR_US_SPIN_LOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_SPIN_LOCK(&(buffer->MR_ppbuffer_lock));
     if (!enough_room_for_variable_size_event(buffer, strlen(message) + 2)) {
         flush_event_buffer(buffer),
         open_block(buffer, MR_ENGINE(MR_eng_id));
@@ -1714,13 +1717,13 @@ MR_threadscope_post_log_msg(const char *message)
         get_current_time_nanosecs());
     put_string_size16(buffer, message);
 
-    MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
 }
 
 void
-MR_threadscope_post_create_engset(MR_EngSetId id, MR_EngSetType type)
+MR_parprof_post_create_engset(MR_EngSetId id, MR_EngSetType type)
 {
-    struct MR_threadscope_event_buffer *buffer = &global_buffer;
+    struct MR_parprof_event_buffer *buffer = &global_buffer;
 
     if (!enough_room_for_event(buffer, MR_TS_EVENT_CAPSET_CREATE)) {
         flush_event_buffer(buffer);
@@ -1732,9 +1735,9 @@ MR_threadscope_post_create_engset(MR_EngSetId id, MR_EngSetType type)
 }
 
 void
-MR_threadscope_post_destroy_engset(MR_EngSetId id)
+MR_parprof_post_destroy_engset(MR_EngSetId id)
 {
-    struct MR_threadscope_event_buffer *buffer = &global_buffer;
+    struct MR_parprof_event_buffer *buffer = &global_buffer;
 
     if (!enough_room_for_event(buffer, MR_TS_EVENT_CAPSET_DELETE)) {
         flush_event_buffer(buffer);
@@ -1746,10 +1749,10 @@ MR_threadscope_post_destroy_engset(MR_EngSetId id)
 }
 
 void
-MR_threadscope_post_engset_add(struct MR_threadscope_event_buffer *buffer,
+MR_parprof_post_engset_add(struct MR_parprof_event_buffer *buffer,
     MR_EngSetId id, MR_EngineId eng)
 {
-    MR_US_SPIN_LOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_SPIN_LOCK(&(buffer->MR_ppbuffer_lock));
     maybe_close_block(buffer);
     if (!enough_room_for_event(buffer, MR_TS_EVENT_CAPSET_ASSIGN_CAP)) {
         flush_event_buffer(buffer);
@@ -1763,15 +1766,15 @@ MR_threadscope_post_engset_add(struct MR_threadscope_event_buffer *buffer,
     put_engset_id(buffer, id);
     put_engine_id(buffer, eng);
 
-    MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
 }
 
 void
-MR_threadscope_post_engset_remove(MR_EngSetId id, MR_EngineId eng)
+MR_parprof_post_engset_remove(MR_EngSetId id, MR_EngineId eng)
 {
-    struct MR_threadscope_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
+    struct MR_parprof_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
 
-    MR_US_SPIN_LOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_SPIN_LOCK(&(buffer->MR_ppbuffer_lock));
     maybe_close_block(buffer);
     if (!enough_room_for_event(buffer, MR_TS_EVENT_CAPSET_REMOVE_CAP)) {
         flush_event_buffer(buffer);
@@ -1782,14 +1785,14 @@ MR_threadscope_post_engset_remove(MR_EngSetId id, MR_EngineId eng)
     put_engset_id(buffer, id);
     put_engine_id(buffer, eng);
 
-    MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
 }
 
 void
-MR_threadscope_post_runtime_identifier(MR_EngSetId engset_id,
+MR_parprof_post_runtime_identifier(MR_EngSetId engset_id,
     const char *identifier)
 {
-    struct MR_threadscope_event_buffer *buffer = &global_buffer;
+    struct MR_parprof_event_buffer *buffer = &global_buffer;
     unsigned len;
 
     len = strlen(identifier);
@@ -1805,11 +1808,11 @@ MR_threadscope_post_runtime_identifier(MR_EngSetId engset_id,
 }
 
 void
-MR_threadscope_post_new_future(MR_Future *future_id, MR_TS_StringId name)
+MR_parprof_post_new_future(MR_Future *future_id, MR_Parprof_StringId name)
 {
-    struct MR_threadscope_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
+    struct MR_parprof_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
 
-    MR_US_SPIN_LOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_SPIN_LOCK(&(buffer->MR_ppbuffer_lock));
     if (!enough_room_for_event(buffer, MR_TS_MER_EVENT_FUT_CREATE)) {
         flush_event_buffer(buffer);
         open_block(buffer, MR_ENGINE(MR_eng_id));
@@ -1822,15 +1825,15 @@ MR_threadscope_post_new_future(MR_Future *future_id, MR_TS_StringId name)
     put_future_id(buffer, future_id);
     put_string_id(buffer, name);
 
-    MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
 }
 
 void
-MR_threadscope_post_wait_future_nosuspend(MR_Future* future_id)
+MR_parprof_post_wait_future_nosuspend(MR_Future* future_id)
 {
-    struct MR_threadscope_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
+    struct MR_parprof_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
 
-    MR_US_SPIN_LOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_SPIN_LOCK(&(buffer->MR_ppbuffer_lock));
     if (!enough_room_for_event(buffer, MR_TS_MER_EVENT_FUT_WAIT_NOSUSPEND)) {
         flush_event_buffer(buffer);
         open_block(buffer, MR_ENGINE(MR_eng_id));
@@ -1842,15 +1845,15 @@ MR_threadscope_post_wait_future_nosuspend(MR_Future* future_id)
         get_current_time_nanosecs());
     put_future_id(buffer, future_id);
 
-    MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
 }
 
 void
-MR_threadscope_post_wait_future_suspended(MR_Future* future_id)
+MR_parprof_post_wait_future_suspended(MR_Future* future_id)
 {
-    struct MR_threadscope_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
+    struct MR_parprof_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
 
-    MR_US_SPIN_LOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_SPIN_LOCK(&(buffer->MR_ppbuffer_lock));
     if (!enough_room_for_event(buffer, MR_TS_MER_EVENT_FUT_WAIT_SUSPENDED)) {
         flush_event_buffer(buffer);
         open_block(buffer, MR_ENGINE(MR_eng_id));
@@ -1862,15 +1865,15 @@ MR_threadscope_post_wait_future_suspended(MR_Future* future_id)
         get_current_time_nanosecs());
     put_future_id(buffer, future_id);
 
-    MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
 }
 
 void
-MR_threadscope_post_signal_future(MR_Future* future_id)
+MR_parprof_post_signal_future(MR_Future* future_id)
 {
-    struct MR_threadscope_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
+    struct MR_parprof_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
 
-    MR_US_SPIN_LOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_SPIN_LOCK(&(buffer->MR_ppbuffer_lock));
     if (!enough_room_for_event(buffer, MR_TS_MER_EVENT_FUT_SIGNAL)) {
         flush_event_buffer(buffer);
         open_block(buffer, MR_ENGINE(MR_eng_id));
@@ -1882,14 +1885,14 @@ MR_threadscope_post_signal_future(MR_Future* future_id)
         get_current_time_nanosecs());
     put_future_id(buffer, future_id);
 
-    MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
 }
 
-void MR_threadscope_post_engine_sleeping(void)
+void MR_parprof_post_engine_sleeping(void)
 {
-    struct MR_threadscope_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
+    struct MR_parprof_event_buffer *buffer = MR_ENGINE(MR_eng_ts_buffer);
 
-    MR_US_SPIN_LOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_SPIN_LOCK(&(buffer->MR_ppbuffer_lock));
     if (!enough_room_for_event(buffer, MR_TS_MER_EVENT_ENGINE_SLEEPING)) {
         flush_event_buffer(buffer);
         open_block(buffer, MR_ENGINE(MR_eng_id));
@@ -1900,21 +1903,21 @@ void MR_threadscope_post_engine_sleeping(void)
     put_event_header(buffer, MR_TS_MER_EVENT_ENGINE_SLEEPING,
         get_current_time_nanosecs());
 
-    MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+    MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
 }
 
 /***************************************************************************/
 
-static struct MR_threadscope_event_buffer*
+static struct MR_parprof_event_buffer*
 MR_create_event_buffer(void)
 {
-    struct MR_threadscope_event_buffer* buffer;
+    struct MR_parprof_event_buffer* buffer;
 
-    buffer = MR_GC_NEW(MR_threadscope_event_buffer_t);
-    buffer->MR_tsbuffer_pos = 0;
-    buffer->MR_tsbuffer_block_open_pos = -1;
-    buffer->MR_tsbuffer_ctxt_is_stopped = MR_TRUE;
-    buffer->MR_tsbuffer_lock = MR_US_LOCK_INITIAL_VALUE;
+    buffer = MR_GC_NEW(MR_parprof_event_buffer_t);
+    buffer->MR_ppbuffer_pos = 0;
+    buffer->MR_ppbuffer_block_open_pos = -1;
+    buffer->MR_ppbuffer_ctxt_is_stopped = MR_TRUE;
+    buffer->MR_ppbuffer_lock = MR_US_LOCK_INITIAL_VALUE;
 
     return buffer;
 }
@@ -1937,16 +1940,16 @@ MR_open_output_file_and_write_prelude(void)
     ** for this filename.
     */
     filename_len = strlen(progname_base) + strlen(MR_TS_FILENAME_FORMAT) + 1;
-    MR_threadscope_output_filename = MR_GC_NEW_ARRAY(char, filename_len);
-    snprintf(MR_threadscope_output_filename, filename_len,
+    MR_parprof_output_filename = MR_GC_NEW_ARRAY(char, filename_len);
+    snprintf(MR_parprof_output_filename, filename_len,
         MR_TS_FILENAME_FORMAT, progname_base);
     free(progname_copy);
     progname_copy = NULL;
     progname_base = NULL;
 
-    MR_threadscope_output_file = fopen(MR_threadscope_output_filename, "w");
-    if (!MR_threadscope_output_file) {
-        perror(MR_threadscope_output_filename);
+    MR_parprof_output_file = fopen(MR_parprof_output_filename, "w");
+    if (!MR_parprof_output_file) {
+        perror(MR_parprof_output_filename);
         return;
     }
 
@@ -1968,20 +1971,20 @@ MR_open_output_file_and_write_prelude(void)
 static void
 MR_close_output_file(void)
 {
-    if (MR_threadscope_output_file) {
+    if (MR_parprof_output_file) {
         put_be_uint16(&global_buffer, MR_TS_EVENT_DATA_END);
         if (flush_event_buffer(&global_buffer)) {
-            if (EOF == fclose(MR_threadscope_output_file)) {
-                perror(MR_threadscope_output_filename);
+            if (EOF == fclose(MR_parprof_output_file)) {
+                perror(MR_parprof_output_filename);
             }
-            MR_threadscope_output_file = NULL;
-            MR_threadscope_output_filename = NULL;
+            MR_parprof_output_file = NULL;
+            MR_parprof_output_filename = NULL;
         }
     }
 }
 
 static void
-put_event_type(struct MR_threadscope_event_buffer *buffer,
+put_event_type(struct MR_parprof_event_buffer *buffer,
     EventTypeDesc *event_type_desc)
 {
     MR_int_least16_t    size;
@@ -2022,47 +2025,47 @@ put_event_type(struct MR_threadscope_event_buffer *buffer,
 }
 
 static MR_bool
-flush_event_buffer(struct MR_threadscope_event_buffer *buffer)
+flush_event_buffer(struct MR_parprof_event_buffer *buffer)
 {
     maybe_close_block(buffer);
 
     /*
     ** fwrite handles locking for us, so we have no concurrent access problems.
     */
-    if (MR_threadscope_output_file && buffer->MR_tsbuffer_pos) {
-        if (0 == fwrite(buffer->MR_tsbuffer_data, buffer->MR_tsbuffer_pos, 1,
-            MR_threadscope_output_file))
+    if (MR_parprof_output_file && buffer->MR_ppbuffer_pos) {
+        if (0 == fwrite(buffer->MR_ppbuffer_data, buffer->MR_ppbuffer_pos, 1,
+            MR_parprof_output_file))
         {
-            perror(MR_threadscope_output_filename);
-            MR_threadscope_output_file = NULL;
-            MR_threadscope_output_filename = NULL;
+            perror(MR_parprof_output_filename);
+            MR_parprof_output_file = NULL;
+            MR_parprof_output_filename = NULL;
         }
     }
-    buffer->MR_tsbuffer_pos = 0;
+    buffer->MR_ppbuffer_pos = 0;
 
-    return (MR_threadscope_output_filename ? MR_TRUE : MR_FALSE);
+    return (MR_parprof_output_filename ? MR_TRUE : MR_FALSE);
 }
 
 static void
-maybe_close_block(struct MR_threadscope_event_buffer *buffer)
+maybe_close_block(struct MR_parprof_event_buffer *buffer)
 {
     MR_Unsigned saved_pos;
 
-    if (buffer->MR_tsbuffer_block_open_pos != -1) {
-        saved_pos = buffer->MR_tsbuffer_pos;
-        buffer->MR_tsbuffer_pos = buffer->MR_tsbuffer_block_open_pos +
+    if (buffer->MR_ppbuffer_block_open_pos != -1) {
+        saved_pos = buffer->MR_ppbuffer_pos;
+        buffer->MR_ppbuffer_pos = buffer->MR_ppbuffer_block_open_pos +
             sizeof(EventType) + sizeof(Time);
         put_eventlog_offset(buffer,
-            saved_pos - buffer->MR_tsbuffer_block_open_pos);
+            saved_pos - buffer->MR_ppbuffer_block_open_pos);
         put_timestamp(buffer, get_current_time_nanosecs());
 
-        buffer->MR_tsbuffer_block_open_pos = -1;
-        buffer->MR_tsbuffer_pos = saved_pos;
+        buffer->MR_ppbuffer_block_open_pos = -1;
+        buffer->MR_ppbuffer_pos = saved_pos;
     }
 }
 
 static void
-open_block(struct MR_threadscope_event_buffer *buffer, MR_Unsigned eng_id)
+open_block(struct MR_parprof_event_buffer *buffer, MR_Unsigned eng_id)
 {
     maybe_close_block(buffer);
 
@@ -2070,13 +2073,13 @@ open_block(struct MR_threadscope_event_buffer *buffer, MR_Unsigned eng_id)
     ** Save the old position. Close block uses this so that it knows
     ** where the block marker is that it should write into.
     */
-    buffer->MR_tsbuffer_block_open_pos = buffer->MR_tsbuffer_pos;
+    buffer->MR_ppbuffer_block_open_pos = buffer->MR_ppbuffer_pos;
 
     put_event_header(buffer, MR_TS_EVENT_BLOCK_MARKER,
         get_current_time_nanosecs());
 
     /* Skip over the next two fields, they are filled in by close_block. */
-    buffer->MR_tsbuffer_pos += sizeof(EventlogOffset) + sizeof(Time);
+    buffer->MR_ppbuffer_pos += sizeof(EventlogOffset) + sizeof(Time);
 
     put_engine_id(buffer, eng_id);
 }
@@ -2084,16 +2087,16 @@ open_block(struct MR_threadscope_event_buffer *buffer, MR_Unsigned eng_id)
 static void
 start_gc_callback(void)
 {
-    struct MR_threadscope_event_buffer  *buffer;
+    struct MR_parprof_event_buffer  *buffer;
     MR_Context                          *context;
 
-    MR_DO_THREADSCOPE_DEBUG(
+    MR_DO_PARPROF_DEBUG(
         fprintf(stderr, "In gc start callback thread: 0x%lx\n", pthread_self())
     );
     if (MR_thread_engine_base == NULL) {
         return;
     }
-    MR_DO_THREADSCOPE_DEBUG(
+    MR_DO_PARPROF_DEBUG(
         fprintf(stderr, "\tEngine: 0x%.16lx\n", MR_thread_engine_base)
     );
     buffer = MR_thread_engine_base->MR_eng_ts_buffer;
@@ -2101,15 +2104,15 @@ start_gc_callback(void)
         /* GC might be running before we're done setting up */
         return;
     }
-    MR_DO_THREADSCOPE_DEBUG(
+    MR_DO_PARPROF_DEBUG(
         fprintf(stderr, "\tBuffer: 0x%.16lx\n", buffer)
     );
 
-    if (MR_US_TRY_LOCK(&(buffer->MR_tsbuffer_lock))) {
+    if (MR_US_TRY_LOCK(&(buffer->MR_ppbuffer_lock))) {
         context = MR_thread_engine_base->MR_eng_this_context;
-        if (!buffer->MR_tsbuffer_ctxt_is_stopped && context) {
-            MR_threadscope_post_stop_context_locked(buffer,
-                context, MR_TS_STOP_REASON_HEAP_OVERFLOW);
+        if (!buffer->MR_ppbuffer_ctxt_is_stopped && context) {
+            MR_parprof_post_stop_context_locked(buffer,
+                context, MR_PARPROF_STOP_REASON_HEAP_OVERFLOW);
         }
 
         if (!enough_room_for_event(buffer, MR_TS_EVENT_GC_START)) {
@@ -2136,17 +2139,17 @@ start_gc_callback(void)
         put_event_header(buffer, MR_TS_EVENT_GC_GLOBAL_SYNC,
             get_current_time_nanosecs());
 
-        MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+        MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
     }
 }
 
 static void
 stop_gc_callback(void)
 {
-    struct MR_threadscope_event_buffer  *buffer;
+    struct MR_parprof_event_buffer      *buffer;
     MR_Context                          *context;
 
-    MR_DO_THREADSCOPE_DEBUG(
+    MR_DO_PARPROF_DEBUG(
         fprintf(stderr, "In gc stop callback thread: 0x%lx\n", pthread_self());
     );
     if (MR_thread_engine_base == NULL) return;
@@ -2156,7 +2159,7 @@ stop_gc_callback(void)
         return;
     }
 
-    if (MR_US_TRY_LOCK(&(buffer->MR_tsbuffer_lock))) {
+    if (MR_US_TRY_LOCK(&(buffer->MR_ppbuffer_lock))) {
         if (!enough_room_for_event(buffer, MR_TS_EVENT_GC_END)) {
             flush_event_buffer(buffer);
             open_block(buffer, MR_thread_engine_base->MR_eng_id);
@@ -2168,20 +2171,20 @@ stop_gc_callback(void)
             get_current_time_nanosecs());
 
         context = MR_thread_engine_base->MR_eng_this_context;
-        if (!buffer->MR_tsbuffer_ctxt_is_stopped && context) {
-            MR_threadscope_post_run_context_locked(buffer, context);
+        if (!buffer->MR_ppbuffer_ctxt_is_stopped && context) {
+            MR_parprof_post_run_context_locked(buffer, context);
         }
-        MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+        MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
     }
 }
 
 static void
 pause_thread_gc_callback(void)
 {
-    struct MR_threadscope_event_buffer  *buffer;
+    struct MR_parprof_event_buffer  *buffer;
     MR_Context                          *context;
 
-    MR_DO_THREADSCOPE_DEBUG(
+    MR_DO_PARPROF_DEBUG(
         fprintf(stderr, "In gc pause thread callback thread: 0x%lx\n",
             pthread_self())
     );
@@ -2192,23 +2195,23 @@ pause_thread_gc_callback(void)
         return;
     }
 
-    if (MR_US_TRY_LOCK(&(buffer->MR_tsbuffer_lock))) {
+    if (MR_US_TRY_LOCK(&(buffer->MR_ppbuffer_lock))) {
         context = MR_thread_engine_base->MR_eng_this_context;
-        if (!buffer->MR_tsbuffer_ctxt_is_stopped && context) {
-            MR_threadscope_post_stop_context_locked(buffer, context,
-                MR_TS_STOP_REASON_YIELDING);
+        if (!buffer->MR_ppbuffer_ctxt_is_stopped && context) {
+            MR_parprof_post_stop_context_locked(buffer, context,
+                MR_PARPROF_STOP_REASON_YIELDING);
         }
-        MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+        MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
     }
 }
 
 static void
 resume_thread_gc_callback(void)
 {
-    struct MR_threadscope_event_buffer  *buffer;
+    struct MR_parprof_event_buffer  *buffer;
     MR_Context                          *context;
 
-    MR_DO_THREADSCOPE_DEBUG(
+    MR_DO_PARPROF_DEBUG(
         fprintf(stderr, "In gc resume thread callback thread: 0x%lx\n",
             pthread_self());
     );
@@ -2219,12 +2222,12 @@ resume_thread_gc_callback(void)
         return;
     }
 
-    if (MR_US_TRY_LOCK(&(buffer->MR_tsbuffer_lock))) {
+    if (MR_US_TRY_LOCK(&(buffer->MR_ppbuffer_lock))) {
         context = MR_thread_engine_base->MR_eng_this_context;
-        if (!buffer->MR_tsbuffer_ctxt_is_stopped && context) {
-            MR_threadscope_post_run_context_locked(buffer, context);
+        if (!buffer->MR_ppbuffer_ctxt_is_stopped && context) {
+            MR_parprof_post_run_context_locked(buffer, context);
         }
-        MR_US_UNLOCK(&(buffer->MR_tsbuffer_lock));
+        MR_US_UNLOCK(&(buffer->MR_ppbuffer_lock));
     }
 }
 
@@ -2233,7 +2236,7 @@ resume_thread_gc_callback(void)
 static Time
 get_current_time_nanosecs(void)
 {
-    if (MR_threadscope_use_tsc) {
+    if (MR_parprof_use_tsc) {
         MR_uint_least64_t   current_tsc;
         MercuryEngine       *eng = MR_thread_engine_base;
 
@@ -2266,4 +2269,4 @@ gettimeofday_nsecs(void)
 
 /***************************************************************************/
 
-#endif /* MR_THREADSCOPE */
+#endif /* MR_PARPROF */
diff --git a/runtime/mercury_par_profile.h b/runtime/mercury_par_profile.h
index b9c43ff..230de4d 100644
--- a/runtime/mercury_par_profile.h
+++ b/runtime/mercury_par_profile.h
@@ -22,52 +22,52 @@
 #include "mercury_engine.h"
 #include "mercury_context.h"
 
-#ifdef MR_THREADSCOPE
+#ifdef MR_PARPROF
 
 /*
 ** Reasons why a context has been stopped, not all of these apply to Mercury,
 ** for instance contexts don't yield.
 */
-#define MR_TS_STOP_REASON_HEAP_OVERFLOW     1
-#define MR_TS_STOP_REASON_STACK_OVERFLOW    2
-#define MR_TS_STOP_REASON_YIELDING          3
-#define MR_TS_STOP_REASON_BLOCKED           4
-#define MR_TS_STOP_REASON_FINISHED          5
+#define MR_PARPROF_STOP_REASON_HEAP_OVERFLOW     1
+#define MR_PARPROF_STOP_REASON_STACK_OVERFLOW    2
+#define MR_PARPROF_STOP_REASON_YIELDING          3
+#define MR_PARPROF_STOP_REASON_BLOCKED           4
+#define MR_PARPROF_STOP_REASON_FINISHED          5
 
-typedef struct MR_threadscope_event_buffer MR_threadscope_event_buffer_t;
+typedef struct MR_parprof_event_buffer MR_parprof_event_buffer_t;
 
 typedef MR_uint_least16_t   MR_ContextStopReason;
 typedef MR_Integer          MR_ContextId;
-typedef MR_uint_least32_t   MR_TS_StringId;
+typedef MR_uint_least32_t   MR_Parprof_StringId;
 typedef MR_uint_least32_t   MR_SparkId;
 typedef MR_uint_least32_t   MR_EngSetId;
 typedef MR_uint_least16_t   MR_EngSetType;
-typedef MR_uint_least32_t   MR_TS_Pid;
+typedef MR_uint_least32_t   MR_Parprof_Pid;
 
-typedef struct MR_Threadscope_String {
-    const char*     MR_tsstring_string;
-    MR_TS_StringId  MR_tsstring_id;
-} MR_Threadscope_String;
+typedef struct MR_Parprof_String {
+    const char*         MR_ppstring_string;
+    MR_Parprof_StringId MR_ppstring_id;
+} MR_Parprof_String;
 
 /*
 ** Set this to true to use the CPU's time stamp counter.
 **
 ** This is initially set in mercury_wrapper.c and may be reset by
-** MR_setup_threadscope if the TSC can't be used.
+** MR_setup_parprof if the TSC can't be used.
 */
-extern MR_bool MR_threadscope_use_tsc;
+extern MR_bool MR_parprof_use_tsc;
 
 /*
 ** This must be called by the primordial thread before starting any other
 ** threads but after the primordial thread has been pinned.
 */
-extern void MR_setup_threadscope(void);
+extern void MR_setup_parprof(void);
 
-extern void MR_finalize_threadscope(void);
+extern void MR_finalize_parprof(void);
 
-extern void MR_threadscope_setup_engine(MercuryEngine *eng);
+extern void MR_parprof_setup_engine(MercuryEngine *eng);
 
-extern void MR_threadscope_finalize_engine(MercuryEngine *eng);
+extern void MR_parprof_finalize_engine(MercuryEngine *eng);
 
 #if 0
 /*
@@ -77,16 +77,16 @@ extern void MR_threadscope_finalize_engine(MercuryEngine *eng);
 */
 /*
 ** Synchronize a slave thread's TSC offset to the master's.  The master thread
-** (with an engine) should call MR_threadscope_sync_tsc_master() for each slave
-** while each slave (with an engine) calls MR_threadscope_sync_tsc_slave().
-** All master - slave pairs must be pinned to CPUs and setup their threadscope
-** structures already (by calling MR_threadscope_setup_engine() above).
+** (with an engine) should call MR_parprof_sync_tsc_master() for each slave
+** while each slave (with an engine) calls MR_parprof_sync_tsc_slave().
+** All master - slave pairs must be pinned to CPUs and setup their parprof
+** structures already (by calling MR_parprof_setup_engine() above).
 ** Multiple slaves may call the _slave at the same time, a lock is used to
 ** synchronize only one at a time.  Only the primordial thread may call
-** MR_threadscope_sync_tsc_master().
+** MR_parprof_sync_tsc_master().
 */
-extern void MR_threadscope_sync_tsc_master(void);
-extern void MR_threadscope_sync_tsc_slave(void);
+extern void MR_parprof_sync_tsc_master(void);
+extern void MR_parprof_sync_tsc_slave(void);
 #endif
 
 /*
@@ -100,9 +100,10 @@ extern void MR_threadscope_sync_tsc_slave(void);
 ** that it doesn't have to be the current context.
 **
 ** Using the MR_Context typedef here requires the inclusion of
-** mercury_context.h, creating a circular dependency
+** mercury_context.h, creating a circular dependency, so instead we use the
+** MR_Context_Struct struct directly.
 */
-extern void MR_threadscope_post_create_context(
+extern void MR_parprof_post_create_context(
                 struct MR_Context_Struct *context);
 
 /*
@@ -110,7 +111,7 @@ extern void MR_threadscope_post_create_context(
 ** event should be posted in addition to (and after) create_thread
 ** above.
 */
-extern void MR_threadscope_post_create_context_for_spark(
+extern void MR_parprof_post_create_context_for_spark(
                 struct MR_Context_Struct *ctxt);
 
 /*
@@ -118,125 +119,126 @@ extern void MR_threadscope_post_create_context_for_spark(
 ** see a new create_context or create_context_for_spark message with the same
 ** context ID, such a message indicates that the context is being re-used.
 */
-extern void MR_threadscope_post_release_context(
+extern void MR_parprof_post_release_context(
                 struct MR_Context_Struct *context);
 
 /*
 ** This context is being reused (after being released). This event is an
 ** alternative to create_context above.
 */
-extern void MR_threadscope_post_reuse_context(
+extern void MR_parprof_post_reuse_context(
                 struct MR_Context_Struct *context, MR_Unsigned old_id);
 
 /*
 ** This message says the context is now ready to run.  Such as it's being
 ** placed on the run queue after being blocked
 */
-extern void MR_threadscope_post_context_runnable(
+extern void MR_parprof_post_context_runnable(
                 struct MR_Context_Struct *context);
 
 /*
 ** This message says we're now running the current context
 */
-extern void MR_threadscope_post_run_context(void);
+extern void MR_parprof_post_run_context(void);
 
 /*
 ** This message says we've stopped executing the current context,
 ** a reason why should be provided.
 */
-extern void MR_threadscope_post_stop_context(MR_ContextStopReason reason);
+extern void MR_parprof_post_stop_context(MR_ContextStopReason reason);
 
 /*
 ** This message says we're about to execute a spark from our local stack.
 */
-extern void MR_threadscope_post_run_spark(MR_SparkId spark_id);
+extern void MR_parprof_post_run_spark(MR_SparkId spark_id);
 
 /*
 ** This message says that we're about to execute a spark that was stolen from
 ** another's stack.
 */
-extern void MR_threadscope_post_steal_spark(MR_SparkId spark_id);
+extern void MR_parprof_post_steal_spark(MR_SparkId spark_id);
 
 /*
 ** This message says that a spark is being created for the given computation.
 ** The spark's ID is given as an argument.
 */
-extern void MR_threadscope_post_sparking(MR_Word* dynamic_conj_id,
+extern void MR_parprof_post_sparking(MR_Word* dynamic_conj_id,
                 MR_SparkId spark_id);
 
 /*
 ** Post this message just before invoking the main/2 predicate.
 */
-extern void MR_threadscope_post_calling_main(void);
+extern void MR_parprof_post_calling_main(void);
 
 /*
 ** Post this message when an engine begins looking for a context to run.
 */
-extern void MR_threadscope_post_looking_for_global_context(void);
+extern void MR_parprof_post_looking_for_global_context(void);
 
 /*
 ** Post this message when an engine begins trying to run a spark from it's
 ** local stack.
 */
-extern void MR_threadscope_post_looking_for_local_spark(void);
+extern void MR_parprof_post_looking_for_local_spark(void);
 
 /*
 ** Post this message when a thread is about to attempt work stealing.
 */
-extern void MR_threadscope_post_work_stealing(void);
+extern void MR_parprof_post_work_stealing(void);
 
 /*
 ** Post this message before a parallel conjunction starts.
 */
-extern void MR_threadscope_post_start_par_conj(MR_Word* dynamic_id,
-                MR_TS_StringId static_id);
+extern void MR_parprof_post_start_par_conj(MR_Word* dynamic_id,
+                MR_Parprof_StringId static_id);
 
 /*
 ** Post this message after a parallel conjunction stops.
 */
-extern void MR_threadscope_post_end_par_conj(MR_Word* dynamic_id);
+extern void MR_parprof_post_end_par_conj(MR_Word* dynamic_id);
 
 /*
 ** Post this message when a parallel conjunct calls the bariier code.
 */
-extern void MR_threadscope_post_end_par_conjunct(MR_Word* dynamic_id);
+extern void MR_parprof_post_end_par_conjunct(MR_Word* dynamic_id);
 
 /*
 ** Post this message when a future is created, this establishes the conjuction
 ** id to future id mapping.  The conjunction id is inferred by context.
 ** The name of the future within the conjunction is given by 'name'.
 */
-extern void MR_threadscope_post_new_future(MR_Future* future_id, MR_TS_StringId name);
+extern void MR_parprof_post_new_future(MR_Future* future_id,
+    MR_Parprof_StringId name);
 
 /*
 ** Post either of these messages when waiting on a future.  THe first if the
 ** context had to be suspended because the future was not available, and the
 ** second when the context did not need to be suspended.
 */
-extern void MR_threadscope_post_wait_future_nosuspend(MR_Future* future_id);
-extern void MR_threadscope_post_wait_future_suspended(MR_Future* future_id);
+extern void MR_parprof_post_wait_future_nosuspend(MR_Future* future_id);
+extern void MR_parprof_post_wait_future_suspended(MR_Future* future_id);
 
 /*
 ** Post this event when signaling the production of a future.
 */
-extern void MR_threadscope_post_signal_future(MR_Future* future_id);
+extern void MR_parprof_post_signal_future(MR_Future* future_id);
 
 /*
 ** Post this event when the engine is going to sleep.
 */
-extern void MR_threadscope_post_engine_sleeping(void);
+extern void MR_parprof_post_engine_sleeping(void);
 
 /*
 ** Register all the strings in an array and save their IDs in the array.
 */
-extern void MR_threadscope_register_strings_array(MR_Threadscope_String *array,
+extern void MR_parprof_register_strings_array(MR_Parprof_String *array,
                 unsigned size);
 
 /*
 ** Post a user-defined log message.
 */
-extern void MR_threadscope_post_log_msg(const char *message);
+extern void MR_parprof_post_log_msg(const char *message);
 
-#endif /* MR_THREADSCOPE */
+#endif /* MR_PARPROF */
 
 #endif /* not MERCURY_PAR_PROFILE_H */
diff --git a/runtime/mercury_thread.c b/runtime/mercury_thread.c
index 780f19a..6460a92 100644
--- a/runtime/mercury_thread.c
+++ b/runtime/mercury_thread.c
@@ -166,8 +166,8 @@ MR_init_thread(MR_when_to_use when_to_use)
 
     MR_all_engine_bases[eng->MR_eng_id] = eng;
     MR_spark_deques[eng->MR_eng_id] = &(eng->MR_eng_spark_deque);
-    #ifdef MR_THREADSCOPE
-        MR_threadscope_setup_engine(eng);
+    #ifdef MR_PARPROF
+        MR_parprof_setup_engine(eng);
     #endif
   #endif
 #else
@@ -179,13 +179,13 @@ MR_init_thread(MR_when_to_use when_to_use)
 #ifdef MR_THREAD_SAFE
     MR_ENGINE(MR_eng_owner_thread) = pthread_self();
   #ifdef MR_LL_PARALLEL_CONJ
-    #ifdef MR_THREADSCOPE
+    #ifdef MR_PARPROF
     /*
     ** TSC Synchronization is not used, support is commented out.  See
     ** runtime/mercury_par_profiling.h for an explanation.
     **
     if (when_to_use == MR_use_later) {
-        MR_threadscope_sync_tsc_slave();
+        MR_parprof_sync_tsc_slave();
     }
     */
     #endif
@@ -215,8 +215,8 @@ MR_init_thread(MR_when_to_use when_to_use)
                         MR_CONTEXT_SIZE_REGULAR, NULL);
             }
             MR_load_context(MR_ENGINE(MR_eng_this_context));
-#ifdef MR_THREADSCOPE
-            MR_threadscope_post_run_context();
+#ifdef MR_PARPROF
+            MR_parprof_post_run_context();
 #endif
             MR_save_registers();
             return MR_TRUE;
diff --git a/runtime/mercury_wrapper.c b/runtime/mercury_wrapper.c
index edb72a9..01224ec 100644
--- a/runtime/mercury_wrapper.c
+++ b/runtime/mercury_wrapper.c
@@ -431,8 +431,8 @@ void    (*MR_address_of_init_modules_complexity)(void);
 void    (*MR_address_of_write_out_proc_statics)(FILE *deep_fp,
             FILE *procrep_fp);
 #endif
-#ifdef  MR_THREADSCOPE
-void    (*MR_address_of_init_modules_threadscope_string_table)(void);
+#ifdef  MR_PARPROF
+void    (*MR_address_of_init_modules_parprof_string_table)(void);
 #endif
 void    (*MR_address_of_init_modules_required)(void);
 void    (*MR_address_of_final_modules_required)(void);
@@ -578,9 +578,9 @@ mercury_runtime_init(int argc, char **argv)
     /*
     ** Setup support for reading the CPU's TSC and detect the clock speed of the
     ** processor. This is currently used by profiling of the parallelism
-    ** runtime and the threadscope support but may be used by other profiling
-    ** or timing code. On architectures other than i386 and amd64 this is a
-    ** no-op.
+    ** runtime and the parallel profiling support but may be used by other
+    ** profiling or timing code. On architectures other than i386 and amd64
+    ** this is a no-op.
     */
     MR_do_cpu_feature_detection();
 #endif
@@ -679,18 +679,18 @@ mercury_runtime_init(int argc, char **argv)
 #if defined(MR_HAVE_THREAD_PINNING)
     MR_pin_primordial_thread();
 #endif
-  #if defined(MR_THREADSCOPE)
+  #if defined(MR_PARPROF)
     /*
-    ** We must setup threadscope before we setup the first engine.
+    ** We must setup parallel profiling before we setup the first engine.
     ** Pin the primordial thread, if thread pinning is configured.
     */
-    MR_setup_threadscope();
+    MR_setup_parprof();
 
     /*
-    ** Setup the threadscope string tables before the standard library is
-    ** initalised or engines are created.
+    ** Setup the parallel profiling string tables before the standard
+    ** library is initalised or engines are created.
     */
-    (*MR_address_of_init_modules_threadscope_string_table)();
+    (*MR_address_of_init_modules_parprof_string_table)();
   #endif
 
 #endif
@@ -710,13 +710,13 @@ mercury_runtime_init(int argc, char **argv)
         for (i = 1; i < MR_num_threads; i++) {
             MR_create_thread(NULL);
         }
-    #ifdef MR_THREADSCOPE
+    #ifdef MR_PARPROF
     /*
     ** TSC Synchronization is not used, support is commented out.
     ** See runtime/mercury_par_profile.h for an explanation.
     **
         for (i = 1; i < MR_num_threads; i++) {
-            MR_threadscope_sync_tsc_master();
+            MR_parprof_sync_tsc_master();
         }
     */
     #endif
@@ -1879,8 +1879,8 @@ MR_process_options(int argc, char **argv)
                 break;
 
             case MR_THREADSCOPE_USE_TSC:
-#ifdef MR_THREADSCOPE
-                MR_threadscope_use_tsc = MR_TRUE;
+#ifdef MR_PARPROF
+                MR_parprof_use_tsc = MR_TRUE;
 #endif
                 break;
 
@@ -2558,9 +2558,9 @@ mercury_runtime_main(void)
         MR_setup_callback(MR_program_entry_point);
 #endif
 
-#ifdef MR_THREADSCOPE
+#ifdef MR_PARPROF
 
-        MR_threadscope_post_calling_main();
+        MR_parprof_post_calling_main();
 
 #endif
 
@@ -2572,9 +2572,9 @@ mercury_runtime_main(void)
         MR_debugmsg0("Returning from MR_call_engine()\n");
 #endif
 
-#ifdef MR_THREADSCOPE
+#ifdef MR_PARPROF
 
-        MR_threadscope_post_stop_context(MR_TS_STOP_REASON_FINISHED);
+        MR_parprof_post_stop_context(MR_PARPROF_STOP_REASON_FINISHED);
 
 #endif
 
@@ -3109,11 +3109,11 @@ mercury_runtime_terminate(void)
 #if !defined(MR_HIGHLEVEL_CODE) && defined(MR_THREAD_SAFE)
     MR_shutdown_all_engines();
 
-#ifdef MR_THREADSCOPE
+#ifdef MR_PARPROF
     if (MR_ENGINE(MR_eng_ts_buffer)) {
-        MR_threadscope_finalize_engine(MR_thread_engine_base);
+        MR_parprof_finalize_engine(MR_thread_engine_base);
     }
-    MR_finalize_threadscope();
+    MR_finalize_parprof();
 #endif
 
     assert(MR_thread_equal(MR_primordial_thread, pthread_self()));
diff --git a/runtime/mercury_wrapper.h b/runtime/mercury_wrapper.h
index 4f7ce48..729df43 100644
--- a/runtime/mercury_wrapper.h
+++ b/runtime/mercury_wrapper.h
@@ -112,9 +112,8 @@ extern void         (*MR_address_of_init_modules_complexity)(void);
 extern void         (*MR_address_of_write_out_proc_statics)(FILE *deep_fp,
                         FILE *procrep_fp);
 #endif
-#ifdef MR_THREADSCOPE
-extern void         (*MR_address_of_init_modules_threadscope_string_table)
-                        (void);
+#ifdef  MR_PARPROF
+extern void         (*MR_address_of_init_modules_parprof_string_table)(void);
 #endif
 extern void         (*MR_address_of_init_modules_required)(void);
 extern void         (*MR_address_of_final_modules_required)(void);
diff --git a/scripts/mgnuc.in b/scripts/mgnuc.in
index e8df6dc..4194cd3 100644
--- a/scripts/mgnuc.in
+++ b/scripts/mgnuc.in
@@ -317,7 +317,7 @@ case $thread_safe in
 esac
 
 case $threadscope in
-    true)       THREADSCOPE_OPTS="-DMR_THREADSCOPE" ;;
+    true)       THREADSCOPE_OPTS="-DMR_PARPROF" ;;
     false)      THREADSCOPE_OPTS="" ;;
 esac
 
diff --git a/util/mkinit.c b/util/mkinit.c
index 0309215..8a99efc 100644
--- a/util/mkinit.c
+++ b/util/mkinit.c
@@ -71,8 +71,8 @@ static const char if_need_term_size[] =
 static const char if_need_deep_prof[] =
     "#if defined(MR_DEEP_PROFILING)\n";
 
-static const char if_need_threadscope[] =
-    "#if defined(MR_THREADSCOPE)\n";
+static const char if_need_parprof[] =
+    "#if defined(MR_PARPROF)\n";
 
 typedef enum
 {
@@ -88,7 +88,7 @@ typedef enum
     PURPOSE_DEBUGGER = 2,
     PURPOSE_COMPLEXITY = 3,
     PURPOSE_PROC_STATIC = 4,
-    PURPOSE_THREADSCOPE_STRING_TABLE = 5,
+    PURPOSE_PARPROF_STRING_TABLE = 5,
     PURPOSE_REQ_INIT = 6,
     PURPOSE_REQ_FINAL = 7
 } Purpose;
@@ -100,7 +100,7 @@ const char  *main_func_name[] =
     "init_modules_debugger",
     "init_modules_complexity_procs",
     "write_out_proc_statics",
-    "init_modules_threadscope_string_table",
+    "init_modules_parprof_string_table",
     "init_modules_required",
     "final_modules_required"
 };
@@ -112,7 +112,7 @@ const char  *module_suffix[] =
     "init_debugger",
     "init_complexity_procs",
     "write_out_proc_statics",
-    "init_threadscope_string_table",
+    "init_parprof_string_table",
     "",
     "",
 };
@@ -136,7 +136,7 @@ const char  *bunch_function_guard[] =
     if_need_to_init,
     if_need_term_size,
     if_need_deep_prof,
-    if_need_threadscope,
+    if_need_parprof,
     NULL,
     NULL,
 };
@@ -148,7 +148,7 @@ const char  *main_func_guard[] =
     NULL,
     if_need_term_size,
     if_need_deep_prof,
-    if_need_threadscope,
+    if_need_parprof,
     NULL,
     NULL,
 };
@@ -421,9 +421,9 @@ static const char mercury_funcs2[] =
     "   MR_address_of_write_out_proc_statics =\n"
     "       write_out_proc_statics;\n"
     "#endif\n"
-    "#ifdef MR_THREADSCOPE\n"
-    "   MR_address_of_init_modules_threadscope_string_table =\n"
-    "       init_modules_threadscope_string_table;\n"
+    "#ifdef MR_PARPROF\n"
+    "   MR_address_of_init_modules_parprof_string_table =\n"
+    "       init_modules_parprof_string_table;\n"
     "#endif\n"
     "   MR_address_of_init_modules_required = init_modules_required;\n"
     "   MR_address_of_final_modules_required = final_modules_required;\n"
@@ -802,9 +802,9 @@ output_init_program(void)
         std_and_special_modules, std_module_next + special_module_next);
     output_main_init_function(PURPOSE_PROC_STATIC, num_bunches);
 
-    num_bunches = output_sub_init_functions(PURPOSE_THREADSCOPE_STRING_TABLE,
+    num_bunches = output_sub_init_functions(PURPOSE_PARPROF_STRING_TABLE,
         std_modules, std_module_next);
-    output_main_init_function(PURPOSE_THREADSCOPE_STRING_TABLE, num_bunches);
+    output_main_init_function(PURPOSE_PARPROF_STRING_TABLE, num_bunches);
 
     num_bunches = output_sub_init_functions(PURPOSE_REQ_INIT,
         req_init_modules, req_init_module_next);
-- 
2.0.0.rc0




More information about the reviews mailing list