[m-rev.] diff: change predicate argument order in set module

Julien Fischer juliensf at csse.unimelb.edu.au
Fri May 6 15:02:26 AEST 2011


Branches: main

Change the argument ordering of predicates in the set module.

library/set.m:
 	Change predicate argument orders to match the versions
 	in the svset module.

 	Group function definitions with the corresponding predicates
 	rather than at the end of the file.

 	Delete Ralph's comments regarding the argument order in the
 	module interface: readers of the library reference guide are
 	unlikely to be interested in his opinion of the argument ordering
 	ten or so years ago.

 	Add extra modes for set.map/3 and set.map_fold/5.

library/svset.m:
library/eqvclass.m:
library/tree234.m:
library/varset.m:
browser/*.m:
compiler/*.m:
deep_profiler/*.m:
mdbcomp/trace_counts.m:
extras/moose/grammar.m:
extras/moose/lalr.m:
extras/moose/moose.m:
tests/hard_coded/bitset_tester.m:
 	Conform to the above change.

NEWS:
 	Announce the above changes.

Julien.

Index: NEWS
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/NEWS,v
retrieving revision 1.563
diff -u -r1.563 NEWS
--- NEWS	5 May 2011 04:35:33 -0000	1.563
+++ NEWS	6 May 2011 04:51:39 -0000
@@ -13,8 +13,8 @@
  * We have improved Unicode support in the standard library.

  * We have changed the argument order of many of the predicates in the
-  bag, bimap, eqvclass, map, multi_map and queue modules in order to make
-  them more conducive to the use of state variable notation.
+  bag, bimap, eqvclass, map, multi_map, queue and set  modules in order
+  to make them more conducive to the use of state variable notation.


  DETAILED LISTING
@@ -29,6 +29,8 @@

      + Text I/O routines now read and write files in UTF-8 encoding.

+* We have added additional modes for set.map/3 and set.map_fold/5.
+
  * The argument order of the following predicates has been changed so as to
    make them more conducive to the use of state variable notation:
    bag.insert/3, bag.insert_list/3, bag.insert_set/3. bag.remove/3,
@@ -47,7 +49,8 @@
    multi_map.remove_smallest/4, queue.put/3, queue.put_list/3,
    queue.get/3, queue.delete_all/3, queue.put_on_front/3,
    queue.get_from_back/3, queue.put_list_on_front/3,
-  queue.get_from_back/3.
+  queue.get_from_back/3, set.insert/3, set.insert_list/3, set.delete/3,
+  set.delete_list/3, set.remove/3, set.remove_list/3 and  set.remove_least/3

  * We have add the following new functions for creating singleton
    maps: bimap.singleton/2, injection.singleton/2, map.singleton/2,
Index: browser/declarative_oracle.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/browser/declarative_oracle.m,v
retrieving revision 1.63
diff -u -r1.63 declarative_oracle.m
--- browser/declarative_oracle.m	5 May 2011 07:11:49 -0000	1.63
+++ browser/declarative_oracle.m	5 May 2011 10:30:53 -0000
@@ -641,15 +641,15 @@
      ),
      (
          Truth = truth_correct,
-        insert(KnownExceptions0 ^ possible, Exception, Possible),
+        set.insert(Exception, KnownExceptions0 ^ possible, Possible),
          KnownExceptions = KnownExceptions0 ^ possible := Possible
      ;
          Truth = truth_erroneous,
-        insert(KnownExceptions0 ^ impossible, Exception, Impossible),
+        set.insert(Exception, KnownExceptions0 ^ impossible, Impossible),
          KnownExceptions = KnownExceptions0 ^ impossible := Impossible
      ;
          Truth = truth_inadmissible,
-        insert(KnownExceptions0 ^ inadmissible, Exception, Inadmissible),
+        set.insert(Exception, KnownExceptions0 ^ inadmissible, Inadmissible),
          KnownExceptions = KnownExceptions0 ^ inadmissible := Inadmissible
      ),
      map.set(Call, KnownExceptions, Map0, Map),
@@ -676,9 +676,9 @@
          map.search(ExceptionsMap0, InitAtom, KnownExceptions0),
          KnownExceptions0 = known_excp(Possible0, Impossible0, Inadmissible0)
      ->
-        set.delete(Possible0, Exception, Possible),
-        set.delete(Impossible0, Exception, Impossible),
-        set.delete(Inadmissible0, Exception, Inadmissible),
+        set.delete(Exception, Possible0, Possible),
+        set.delete(Exception, Impossible0, Impossible),
+        set.delete(Exception, Inadmissible0, Inadmissible),
          KnownExceptions = known_excp(Possible, Impossible, Inadmissible),
          map.set(InitAtom, KnownExceptions, ExceptionsMap0, ExceptionsMap)
      ;
Index: browser/interactive_query.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/browser/interactive_query.m,v
retrieving revision 1.31
diff -u -r1.31 interactive_query.m
--- browser/interactive_query.m	30 Dec 2007 11:11:06 -0000	1.31
+++ browser/interactive_query.m	5 May 2011 07:12:25 -0000
@@ -610,7 +610,7 @@
              % Call the procedure whose address
              % we just obtained.
              %
-            call(QueryPred, !IO)
+            QueryPred(!IO)
          ),
          %
          % unload the object code in the libquery.so file
Index: compiler/accumulator.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/accumulator.m,v
retrieving revision 1.84
diff -u -r1.84 accumulator.m
--- compiler/accumulator.m	5 May 2011 03:58:52 -0000	1.84
+++ compiler/accumulator.m	5 May 2011 12:59:28 -0000
@@ -785,8 +785,8 @@
      ( K =< 0 ->
          set.init(Set)
      ;
-        Set0 = set_upto(Case, K-1),
-        set.insert(Set0, accu_goal_id(Case, K), Set)
+        Set0 = set_upto(Case, K - 1),
+        set.insert(accu_goal_id(Case, K), Set0, Set)
      ).

  %-----------------------------------------------------------------------------%
Index: compiler/add_pragma.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/add_pragma.m,v
retrieving revision 1.115
diff -u -r1.115 add_pragma.m
--- compiler/add_pragma.m	5 May 2011 07:11:50 -0000	1.115
+++ compiler/add_pragma.m	5 May 2011 11:13:34 -0000
@@ -1537,8 +1537,8 @@
              list.map((pred(ProcId::in, PredProcId::out) is det :-
                      PredProcId = proc(PredId, ProcId)
                  ), ProcIds, PredProcIds),
-            set.insert_list(ProcsToSpec0, PredProcIds, ProcsToSpec),
-            set.insert(ForceVersions0, NewPredId, ForceVersions),
+            set.insert_list(PredProcIds, ProcsToSpec0, ProcsToSpec),
+            set.insert(NewPredId, ForceVersions0, ForceVersions),

              ( Status = status_opt_imported ->
                  % For imported predicates dead_proc_elim.m needs to know that
@@ -2416,7 +2416,7 @@
          % Do we have to make sure the tabled preds are stratified?
          ( eval_method_needs_stratification(EvalMethod) = yes ->
              module_info_get_stratified_preds(!.ModuleInfo, StratPredIds0),
-            set.insert(StratPredIds0, PredId, StratPredIds),
+            set.insert(PredId, StratPredIds0, StratPredIds),
              module_info_set_stratified_preds(StratPredIds, !ModuleInfo)
          ;
              true
Index: compiler/arg_info.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/arg_info.m,v
retrieving revision 1.61
diff -u -r1.61 arg_info.m
--- compiler/arg_info.m	3 May 2011 04:34:53 -0000	1.61
+++ compiler/arg_info.m	5 May 2011 13:36:46 -0000
@@ -119,7 +119,6 @@
  :- import_module pair.
  :- import_module require.
  :- import_module int.
-:- import_module svset.

  %-----------------------------------------------------------------------------%
  %
@@ -357,13 +356,13 @@
      mode_to_arg_mode(ModuleInfo, Mode, Type, ArgMode),
      (
          ArgMode = top_in,
-        svset.insert(Var, !Inputs)
+        set.insert(Var, !Inputs)
      ;
          ArgMode = top_out,
-        svset.insert(Var, !Outputs)
+        set.insert(Var, !Outputs)
      ;
          ArgMode = top_unused,
-        svset.insert(Var, !Unuseds)
+        set.insert(Var, !Unuseds)
      ),
      partition_proc_args_2(Vars, Types, Modes, ModuleInfo,
          !Inputs, !Outputs, !Unuseds).
Index: compiler/assertion.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/assertion.m,v
retrieving revision 1.70
diff -u -r1.70 assertion.m
--- compiler/assertion.m	3 May 2011 04:34:53 -0000	1.70
+++ compiler/assertion.m	5 May 2011 11:00:11 -0000
@@ -659,7 +659,7 @@
  update_pred_info(AssertId, PredId, !Module) :-
      module_info_pred_info(!.Module, PredId, PredInfo0),
      pred_info_get_assertions(PredInfo0, Assertions0),
-    set.insert(Assertions0, AssertId, Assertions),
+    set.insert(AssertId, Assertions0, Assertions),
      pred_info_set_assertions(Assertions, PredInfo0, PredInfo),
      module_info_set_pred_info(PredId, PredInfo, !Module).

Index: compiler/basic_block.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/basic_block.m,v
retrieving revision 1.37
diff -u -r1.37 basic_block.m
--- compiler/basic_block.m	3 May 2011 04:34:53 -0000	1.37
+++ compiler/basic_block.m	5 May 2011 13:36:59 -0000
@@ -98,7 +98,6 @@
  :- import_module ll_backend.opt_util.

  :- import_module require.
-:- import_module svset.

  %-----------------------------------------------------------------------------%

@@ -128,7 +127,7 @@
      ;
          counter.allocate(N, !C),
          Label = internal_label(N, ProcLabel),
-        svset.insert(Label, !NewLabels),
+        set.insert(Label, !NewLabels),
          LabelInstr = llds_instr(label(Label), ""),
          RestInstrs = [OrigInstr0 | OrigInstrs0]
      ),
Index: compiler/bytecode_gen.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/bytecode_gen.m,v
retrieving revision 1.126
diff -u -r1.126 bytecode_gen.m
--- compiler/bytecode_gen.m	5 May 2011 07:11:50 -0000	1.126
+++ compiler/bytecode_gen.m	5 May 2011 10:33:26 -0000
@@ -138,7 +138,7 @@

      goal_util.goal_vars(Goal, GoalVars),
      proc_info_get_headvars(ProcInfo, ArgVars),
-    set.insert_list(GoalVars, ArgVars, Vars),
+    set.insert_list(ArgVars, GoalVars, Vars),
      set.to_sorted_list(Vars, VarList),
      map.init(VarMap0),
      create_varmap(VarList, VarSet, VarTypes, 0, VarMap0, VarMap, VarInfos),
Index: compiler/call_gen.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/call_gen.m,v
retrieving revision 1.200
diff -u -r1.200 call_gen.m
--- compiler/call_gen.m	27 Jan 2011 08:03:52 -0000	1.200
+++ compiler/call_gen.m	5 May 2011 11:23:26 -0000
@@ -230,7 +230,7 @@
          NonVarCode, !CI),

      extra_livevals(FirstImmInput, ExtraLiveVals),
-    set.insert_list(LiveVals0, ExtraLiveVals, LiveVals),
+    set.insert_list(ExtraLiveVals, LiveVals0, LiveVals),

      call_gen.prepare_for_call(CodeModel, CallModel, TraceCode, !CI),

@@ -575,23 +575,22 @@
  :- pred find_nonlive_outputs(assoc_list(prog_var, arg_info)::in,
      set(prog_var)::in, set(prog_var)::in, set(prog_var)::out) is det.

-find_nonlive_outputs([], _, NonLiveOutputs, NonLiveOutputs).
+find_nonlive_outputs([], _, !NonLiveOutputs).
  find_nonlive_outputs([Var - arg_info(_ArgLoc, Mode) | Args],
-        Liveness, NonLiveOutputs0, NonLiveOutputs) :-
+        Liveness, !NonLiveOutputs) :-
      (
          Mode = top_out,
          ( set.member(Var, Liveness) ->
-            NonLiveOutputs1 = NonLiveOutputs0
+            true
          ;
-            set.insert(NonLiveOutputs0, Var, NonLiveOutputs1)
+            set.insert(Var, !NonLiveOutputs)
          )
      ;
          ( Mode = top_in
          ; Mode = top_unused
-        ),
-        NonLiveOutputs1 = NonLiveOutputs0
+        )
      ),
-    find_nonlive_outputs(Args, Liveness, NonLiveOutputs1, NonLiveOutputs).
+    find_nonlive_outputs(Args, Liveness, !NonLiveOutputs).

  :- pred rebuild_registers(assoc_list(prog_var, arg_info)::in,
      set(prog_var)::in, assoc_list(prog_var, arg_loc)::out,
Index: compiler/check_typeclass.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/check_typeclass.m,v
retrieving revision 1.133
diff -u -r1.133 check_typeclass.m
--- compiler/check_typeclass.m	5 May 2011 07:11:50 -0000	1.133
+++ compiler/check_typeclass.m	5 May 2011 13:37:07 -0000
@@ -133,7 +133,6 @@
  :- import_module set.
  :- import_module solutions.
  :- import_module string.
-:- import_module svset.
  :- import_module term.
  :- import_module varset.

@@ -1042,7 +1041,7 @@
          ),
          Ancestors = ClassDefn0 ^ class_fundep_ancestors
      ;
-        svset.insert(ClassId, !Visited),
+        set.insert(ClassId, !Visited),

          % Make this class its own ancestor, but only if it has fundeps on it.
          FunDeps = ClassDefn0 ^ class_fundeps,
@@ -1339,7 +1338,7 @@
          each_arg_is_a_distinct_type_variable(!.SeenTypes, Args, 1, Result),
          (
              Result = no_error,
-            svset.insert_list(Args, !SeenTypes)
+            set.insert_list(Args, !SeenTypes)
          ;
              ( Result = local_non_distinct
              ; Result = global_non_distinct
@@ -1356,7 +1355,7 @@
          each_arg_is_a_distinct_type_variable(!.SeenTypes, Args, 1, Result),
          (
              Result = no_error,
-            svset.insert_list(Args, !SeenTypes),
+            set.insert_list(Args, !SeenTypes),
              ( type_to_type_defn(ModuleInfo, Type, TypeDefn) ->
                  list.length(Args, TypeArity),
                  is_visible_instance_type(TypeName, TypeArity, TypeDefn,
Index: compiler/closure_analysis.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/closure_analysis.m,v
retrieving revision 1.22
diff -u -r1.22 closure_analysis.m
--- compiler/closure_analysis.m	3 May 2011 04:34:53 -0000	1.22
+++ compiler/closure_analysis.m	5 May 2011 13:37:18 -0000
@@ -53,7 +53,6 @@
  :- import_module require.
  :- import_module set.
  :- import_module string.
-:- import_module svset.
  :- import_module varset.

  %----------------------------------------------------------------------------%
@@ -237,7 +236,7 @@
          % separately.

          ( Details = higher_order(CalledClosure0, _, _, _) ->
-            svset.insert(CalledClosure0, InputArgs0, InputArgs)
+            set.insert(CalledClosure0, InputArgs0, InputArgs)
          ;
              InputArgs = InputArgs0
          ),
@@ -403,9 +402,9 @@
          !Inputs, !Outputs) :-
      ( var_has_ho_type(VarTypes, Var) ->
          ( mode_is_input(ModuleInfo, Mode) ->
-            svset.insert(Var, !Inputs)
+            set.insert(Var, !Inputs)
          ; mode_is_output(ModuleInfo, Mode) ->
-            svset.insert(Var, !Outputs)
+            set.insert(Var, !Outputs)
          ;
              true
          )
Index: compiler/code_info.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/code_info.m,v
retrieving revision 1.384
diff -u -r1.384 code_info.m
--- compiler/code_info.m	3 May 2011 04:34:53 -0000	1.384
+++ compiler/code_info.m	5 May 2011 11:27:48 -0000
@@ -4092,7 +4092,7 @@
      ( variable_is_forward_live(CI, Var) ->
          true
      ;
-        set.insert(!.DeadVars, Var, !:DeadVars)
+        set.insert(Var, !DeadVars)
      ),
      which_variables_are_forward_live(CI, Vars, !DeadVars).

@@ -4218,7 +4218,7 @@
  generate_stack_var_vn(_, [], !Vals).
  generate_stack_var_vn(CI, [V | Vs], !Vals) :-
      get_variable_slot(CI, V, Lval),
-    set.insert(!.Vals, Lval, !:Vals),
+    set.insert(Lval, !Vals),
      generate_stack_var_vn(CI, Vs, !Vals).

  :- pred generate_call_temp_vn(assoc_list(lval, slot_contents)::in,
@@ -4226,7 +4226,7 @@

  generate_call_temp_vn([], !Vals).
  generate_call_temp_vn([Lval - _ | Temps], !Vals) :-
-    set.insert(!.Vals, Lval, !:Vals),
+    set.insert(Lval, !Vals),
      generate_call_temp_vn(Temps, !Vals).

  :- pred generate_input_var_vn(list(arg_loc)::in,
@@ -4235,7 +4235,7 @@
  generate_input_var_vn([], !Vals).
  generate_input_var_vn([InputArgLoc | InputArgLocs], !Vals) :-
      code_util.arg_loc_to_register(InputArgLoc, Lval),
-    set.insert(!.Vals, Lval, !:Vals),
+    set.insert(Lval, !Vals),
      generate_input_var_vn(InputArgLocs, !Vals).

  %---------------------------------------------------------------------------%
@@ -4375,12 +4375,12 @@
      ;
          new_temp_slot(Item, StackVar, !CI)
      ),
-    set.insert(TempsInUse0, StackVar, TempsInUse),
+    set.insert(StackVar, TempsInUse0, TempsInUse),
      set_temps_in_use(TempsInUse, !CI),
      (
          Persistence = persistent_temp_slot,
          get_persistent_temps(!.CI, PersistentTemps0),
-        set.insert(PersistentTemps0, StackVar, PersistentTemps),
+        set.insert(StackVar, PersistentTemps0, PersistentTemps),
          set_persistent_temps(PersistentTemps, !CI)
      ;
          Persistence = non_persistent_temp_slot
@@ -4408,12 +4408,12 @@
          new_temp_slots([HeadItem | TailItems], StackVars,
              StackId, FirstSlotNum, LastSlotNum, !CI)
      ),
-    set.insert_list(TempsInUse0, StackVars, TempsInUse),
+    set.insert_list(StackVars, TempsInUse0, TempsInUse),
      set_temps_in_use(TempsInUse, !CI),
      (
          Persistence = persistent_temp_slot,
          get_persistent_temps(!.CI, PersistentTemps0),
-        set.insert_list(PersistentTemps0, StackVars, PersistentTemps),
+        set.insert_list(StackVars, PersistentTemps0, PersistentTemps),
          set_persistent_temps(PersistentTemps, !CI)
      ;
          Persistence = non_persistent_temp_slot
@@ -4536,7 +4536,7 @@

  release_temp_slot(StackVar, Persistence, !CI) :-
      get_temps_in_use(!.CI, TempsInUse0),
-    set.delete(TempsInUse0, StackVar, TempsInUse),
+    set.delete(StackVar, TempsInUse0, TempsInUse),
      set_temps_in_use(TempsInUse, !CI),

      get_persistent_temps(!.CI, PersistentTemps0),
@@ -4545,7 +4545,7 @@
          Persistence = persistent_temp_slot,
          expect(unify(IsInPersistentTemps0, yes),
              this_file, "released stack slot should be persistent"),
-        set.delete(PersistentTemps0, StackVar, PersistentTemps),
+        set.delete(StackVar, PersistentTemps0, PersistentTemps),
          set_persistent_temps(PersistentTemps, !CI)
      ;
          Persistence = non_persistent_temp_slot,
Index: compiler/continuation_info.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/continuation_info.m,v
retrieving revision 1.101
diff -u -r1.101 continuation_info.m
--- compiler/continuation_info.m	3 May 2011 04:34:53 -0000	1.101
+++ compiler/continuation_info.m	5 May 2011 13:37:51 -0000
@@ -416,7 +416,6 @@
  :- import_module require.
  :- import_module solutions.
  :- import_module string.
-:- import_module svset.
  :- import_module term.
  :- import_module varset.

@@ -712,7 +711,7 @@
      ;
          generate_resume_layout_for_var(Var, LvalSet, InstMap, ProcInfo,
              ModuleInfo, VarInfo, TypeVars),
-        set.insert_list(!.TVars, TypeVars, !:TVars),
+        set.insert_list(TypeVars, !TVars),
          !:VarInfos = [VarInfo | !.VarInfos]
      ),
      generate_resume_layout_for_vars(VarLvals, InstMap, VarTypes, ProcInfo,
@@ -817,7 +816,7 @@
      set.singleton_set(Locations, reg(reg_r, ArgLoc)),
      map.det_insert(Var, Locations, !VarLocs),
      type_vars(Type, VarTypeVars),
-    svset.insert_list(VarTypeVars, !TypeVars),
+    set.insert_list(VarTypeVars, !TypeVars),
      build_closure_info(Vars, Types, ArgInfos, Layouts, InstMap,
          !VarLocs, !TypeVars).

@@ -879,7 +878,7 @@
      map.lookup(VarTypes, Var, Type),
      ArgLayout = table_arg_info(VarNum, VarName, SlotNum, Type),
      type_vars(Type, VarTypeVars),
-    svset.insert_list(VarTypeVars, !TypeVars),
+    set.insert_list(VarTypeVars, !TypeVars),
      build_table_arg_info(VarSet, VarTypes, NumberedVars,
          ArgLayouts, !TypeVars).

Index: compiler/ctgc.selector.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/ctgc.selector.m,v
retrieving revision 1.31
diff -u -r1.31 ctgc.selector.m
--- compiler/ctgc.selector.m	3 May 2011 05:12:03 -0000	1.31
+++ compiler/ctgc.selector.m	5 May 2011 13:37:58 -0000
@@ -99,7 +99,6 @@
  :- import_module set.
  :- import_module solutions.
  :- import_module string.
-:- import_module svset.

  %-----------------------------------------------------------------------------%

@@ -309,7 +308,7 @@
              type_contains_subtype_2(ModuleInfo, ToType, !Queue, !SeenTypes,
                  Contains)
          ;
-            svset.insert(FromType, !SeenTypes),
+            set.insert(FromType, !SeenTypes),
              type_arg_types(ModuleInfo, FromType, ArgTypes),
              ( list.member(ToType, ArgTypes) ->
                  Contains = yes
Index: compiler/deforest.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/deforest.m,v
retrieving revision 1.99
diff -u -r1.99 deforest.m
--- compiler/deforest.m	5 May 2011 03:58:53 -0000	1.99
+++ compiler/deforest.m	5 May 2011 13:03:14 -0000
@@ -726,7 +726,7 @@
                  pd_debug_message(DebugPD, "Pushing call to %s into goal\n",
                      [s(CurrPredName)], !IO)
              ),
-            set.insert(Parents0, proc(PredId, ProcId), Parents),
+            set.insert(proc(PredId, ProcId), Parents0, Parents),
              pd_info_set_parents(Parents, !PDInfo),
              push_goal_into_goal(ConjNonLocals, DeforestBranches,
                  EarlierGoal, BetweenGoals, LaterGoal, Goal, !PDInfo),
@@ -1248,7 +1248,7 @@
              pd_term.update_global_term_info(ProcPair, PredProcId,
                  Size, TermInfo0, TermInfo),
              pd_info_set_global_term_info(TermInfo, !PDInfo),
-            set.insert_list(Parents0, [PredProcId | CalledPreds], Parents),
+            set.insert_list([PredProcId | CalledPreds], Parents0, Parents),
              pd_info_set_parent_versions(Parents, !PDInfo),
              pd_info.register_version(PredProcId, VersionInfo, !PDInfo),

@@ -1742,7 +1742,7 @@
      EarlierGoal = hlds_goal(EarlierGoalExpr, _),
      (
          EarlierGoalExpr = switch(Var1, CanFail1, Cases1),
-        set.insert(NonLocals, Var1, CaseNonLocals),
+        set.insert(Var1, NonLocals, CaseNonLocals),
          append_goal_to_cases(Var1, BetweenGoals, LaterGoal,
              CaseNonLocals, 1, DeforestInfo, Cases1, Cases, !PDInfo),
          GoalExpr = switch(Var1, CanFail1, Cases)
Index: compiler/delay_construct.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/delay_construct.m,v
retrieving revision 1.32
diff -u -r1.32 delay_construct.m
--- compiler/delay_construct.m	30 Dec 2010 11:17:53 -0000	1.32
+++ compiler/delay_construct.m	5 May 2011 13:03:52 -0000
@@ -210,7 +210,7 @@
          instmap_lookup_var(InstMap1, Var, Inst1),
          inst_is_ground(DelayInfo ^ dci_module_info, Inst1)
      ->
-        set.insert(ConstructedVars0, Var, ConstructedVars1),
+        set.insert(Var, ConstructedVars0, ConstructedVars1),
          RevDelayedGoals1 = [Goal0 | RevDelayedGoals0],
          delay_construct_in_conj(Goals0, InstMap1, DelayInfo,
              ConstructedVars1, RevDelayedGoals1, Goals)
Index: compiler/dependency_graph.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/dependency_graph.m,v
retrieving revision 1.107
diff -u -r1.107 dependency_graph.m
--- compiler/dependency_graph.m	7 Mar 2011 03:59:23 -0000	1.107
+++ compiler/dependency_graph.m	5 May 2011 13:38:04 -0000
@@ -130,7 +130,6 @@
  :- import_module pair.
  :- import_module set.
  :- import_module std_util.
-:- import_module svset.
  :- import_module term.
  :- import_module varset.

@@ -709,7 +708,7 @@
          % is not merged into the current sub-module.
          (
              IsAgg = yes,
-            svset.insert(CalledSCCid, !NoMerge)
+            set.insert(CalledSCCid, !NoMerge)
          ;
              IsAgg = no
          ),
Index: compiler/deps_map.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/deps_map.m,v
retrieving revision 1.4
diff -u -r1.4 deps_map.m
--- compiler/deps_map.m	3 May 2011 04:34:53 -0000	1.4
+++ compiler/deps_map.m	5 May 2011 12:35:55 -0000
@@ -123,7 +123,7 @@
      deps_map::in, deps_map::out, io::di, io::uo) is det.

  generate_deps_map_loop(Globals, !.Modules, Search, !DepsMap, !IO) :-
-    ( set.remove_least(!.Modules, Module, !:Modules) ->
+    ( set.remove_least(Module, !Modules) ->
          generate_deps_map_step(Globals, Module, !Modules, Search, !DepsMap,
              !IO),
          generate_deps_map_loop(Globals, !.Modules, Search, !DepsMap, !IO)
Index: compiler/distance_granularity.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/distance_granularity.m,v
retrieving revision 1.13
diff -u -r1.13 distance_granularity.m
--- compiler/distance_granularity.m	30 Dec 2010 11:17:53 -0000	1.13
+++ compiler/distance_granularity.m	5 May 2011 13:05:23 -0000
@@ -519,7 +519,7 @@
          % The non-locals of the hlds_goal_info of the if_then_else goal must
          % contain the variable controlling the granularity.
          NonLocals0 = goal_info_get_nonlocals(ConjInfo),
-        set.insert(NonLocals0, GranularityVar, NonLocals),
+        set.insert(GranularityVar, NonLocals0, NonLocals),
          goal_info_set_nonlocals(NonLocals, ConjInfo, IfThenElseInfo),
          IfThenElseGoal = hlds_goal(if_then_else([], Cond, Then, Else),
              IfThenElseInfo)
@@ -982,7 +982,7 @@
          % Update the nonlocals and the instmap_delta of the hlds_goal_info
          % of the recursive plain call for Var.
          NonLocals0 = goal_info_get_nonlocals(CallInfo0),
-        set.insert(NonLocals0, Var, NonLocals),
+        set.insert(Var, NonLocals0, NonLocals),
          goal_info_set_nonlocals(NonLocals, CallInfo0, CallInfo1),
          InstMapDelta0 = goal_info_get_instmap_delta(CallInfo1),
          MerInst = ground(shared, none),
Index: compiler/dupelim.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/dupelim.m,v
retrieving revision 1.98
diff -u -r1.98 dupelim.m
--- compiler/dupelim.m	3 May 2011 04:34:53 -0000	1.98
+++ compiler/dupelim.m	5 May 2011 13:38:12 -0000
@@ -69,7 +69,6 @@
  :- import_module maybe.
  :- import_module require.
  :- import_module set.
-:- import_module svset.

  %-----------------------------------------------------------------------------%

@@ -132,7 +131,7 @@
      ),
      (
          MaybeFallThrough = yes(FallIntoLabel),
-        svset.insert(FallIntoLabel, !Fixed)
+        set.insert(FallIntoLabel, !Fixed)
      ;
          MaybeFallThrough = no
      ),
@@ -150,25 +149,25 @@
      ->
          (
              MaybeFixedLabel = yes(FixedLabel),
-            svset.insert(FixedLabel, !FoldFixed)
+            set.insert(FixedLabel, !FoldFixed)
          ;
              MaybeFixedLabel = no
          ),
          (
              MaybeLayoutLabel = yes(LayoutLabel),
-            svset.insert(LayoutLabel, !FoldFixed)
+            set.insert(LayoutLabel, !FoldFixed)
          ;
              MaybeLayoutLabel = no
          ),
          (
              MaybeOnlyLayoutLabel = yes(OnlyLayoutLabel),
-            svset.insert(OnlyLayoutLabel, !FoldFixed)
+            set.insert(OnlyLayoutLabel, !FoldFixed)
          ;
              MaybeOnlyLayoutLabel = no
          ),
          (
              MaybeDefLabel = yes(DefLabel),
-            svset.insert(DefLabel, !FoldFixed)
+            set.insert(DefLabel, !FoldFixed)
          ;
              MaybeDefLabel = no
          )
Index: compiler/equiv_type.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/equiv_type.m,v
retrieving revision 1.90
diff -u -r1.90 equiv_type.m
--- compiler/equiv_type.m	3 May 2011 04:34:54 -0000	1.90
+++ compiler/equiv_type.m	5 May 2011 12:36:18 -0000
@@ -1557,7 +1557,7 @@
          % We don't need to record local types.
          ExpandedItemSet = ExpandedItemSet0
      ;
-        set.insert(Items0, ItemId, Items),
+        set.insert(ItemId, Items0, Items),
          ExpandedItemSet = ModuleName - Items
      ).

Index: compiler/equiv_type_hlds.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/equiv_type_hlds.m,v
retrieving revision 1.64
diff -u -r1.64 equiv_type_hlds.m
--- compiler/equiv_type_hlds.m	3 May 2011 04:34:54 -0000	1.64
+++ compiler/equiv_type_hlds.m	5 May 2011 13:46:23 -0000
@@ -54,7 +54,6 @@
  :- import_module pair.
  :- import_module require.
  :- import_module set.
-:- import_module svset.
  :- import_module term.
  :- import_module varset.

@@ -120,7 +119,7 @@

  add_type_ctors_to_set(Type, !Set) :-
      ( type_to_ctor_and_args(Type, TypeCtor, Args) ->
-        svset.insert(TypeCtor, !Set),
+        set.insert(TypeCtor, !Set),
          list.foldl(add_type_ctors_to_set, Args, !Set)
      ;
          true
Index: compiler/erl_code_util.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/erl_code_util.m,v
retrieving revision 1.23
diff -u -r1.23 erl_code_util.m
--- compiler/erl_code_util.m	5 May 2011 03:58:53 -0000	1.23
+++ compiler/erl_code_util.m	5 May 2011 13:38:22 -0000
@@ -215,7 +215,6 @@
  :- import_module map.
  :- import_module require.
  :- import_module set.
-:- import_module svset.
  :- import_module term.
  :- import_module varset.

@@ -312,7 +311,7 @@

  erl_gen_info_add_env_var_name(Name, !Info) :-
      EnvVarNames0 = !.Info ^ egi_env_var_names,
-    set.insert(EnvVarNames0, Name, EnvVarNames),
+    set.insert(Name, EnvVarNames0, EnvVarNames),
      !Info ^ egi_env_var_names := EnvVarNames.

  erl_gen_info_get_env_vars(Info, Info ^ egi_env_var_names).
@@ -823,7 +822,7 @@
          erl_vars_in_exprs(Exprs, !Set)
      ;
          Term = elds_var(Var),
-        svset.insert(Var, !Set)
+        set.insert(Var, !Set)
      ).

  :- pred erl_vars_in_call_target(elds_call_target::in,
Index: compiler/frameopt.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/frameopt.m,v
retrieving revision 1.123
diff -u -r1.123 frameopt.m
--- compiler/frameopt.m	3 May 2011 05:12:03 -0000	1.123
+++ compiler/frameopt.m	5 May 2011 13:38:34 -0000
@@ -167,7 +167,6 @@
  :- import_module require.
  :- import_module set.
  :- import_module string.
-:- import_module svset.

  %-----------------------------------------------------------------------------%

@@ -1676,7 +1675,7 @@
              !:CanTransform = cannot_transform
          ; queue.get(Label, !Queue) ->
              !:PropagationStepsLeft = !.PropagationStepsLeft - 1,
-            svset.insert(Label, !AlreadyProcessed),
+            set.insert(Label, !AlreadyProcessed),
              map.lookup(BlockMap, Label, BlockInfo),
              BlockType = BlockInfo ^ fb_type,
              (
Index: compiler/goal_form.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/goal_form.m,v
retrieving revision 1.51
diff -u -r1.51 goal_form.m
--- compiler/goal_form.m	30 Dec 2010 11:17:54 -0000	1.51
+++ compiler/goal_form.m	5 May 2011 11:01:52 -0000
@@ -226,7 +226,7 @@
          GoalExpr = scope(Reason, _),
          Reason = from_ground_term(Var, from_ground_term_construct)
      ),
-    set.delete(!.ToAssignVars, Var, !:ToAssignVars),
+    set.delete(Var, !ToAssignVars),
      only_constant_goals(Goals, !ToAssignVars).

  %-----------------------------------------------------------------------------%
Index: compiler/goal_util.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/goal_util.m,v
retrieving revision 1.183
diff -u -r1.183 goal_util.m
--- compiler/goal_util.m	5 May 2011 03:58:54 -0000	1.183
+++ compiler/goal_util.m	5 May 2011 11:03:34 -0000
@@ -453,7 +453,6 @@
  :- import_module require.
  :- import_module solutions.
  :- import_module string.
-:- import_module svset.
  :- import_module varset.

  %-----------------------------------------------------------------------------%
@@ -547,11 +546,11 @@
      Goal = hlds_goal(GoalExpr, _GoalInfo),
      (
          GoalExpr = unify(Var, RHS, _, Unif, _),
-        svset.insert(Var, !Set),
+        set.insert(Var, !Set),
          (
              Unif = construct(_, _, _, _, CellToReuse, _, _),
              ( CellToReuse = reuse_cell(cell_to_reuse(Var, _, _)) ->
-                svset.insert(Var, !Set)
+                set.insert(Var, !Set)
              ;
                  true
              )
@@ -568,11 +567,11 @@
      ;
          GoalExpr = generic_call(GenericCall, ArgVars, _, _),
          generic_call_vars(GenericCall, GenericCallVars),
-        svset.insert_list(GenericCallVars, !Set),
-        svset.insert_list(ArgVars, !Set)
+        set.insert_list(GenericCallVars, !Set),
+        set.insert_list(ArgVars, !Set)
      ;
          GoalExpr = plain_call(_, _, ArgVars, _, _, _),
-        svset.insert_list(ArgVars, !Set)
+        set.insert_list(ArgVars, !Set)
      ;
          ( GoalExpr = conj(_, Goals)
          ; GoalExpr = disj(Goals)
@@ -580,22 +579,22 @@
          goals_goal_vars(Goals, !Set)
      ;
          GoalExpr = switch(Var, _Det, Cases),
-        svset.insert(Var, !Set),
+        set.insert(Var, !Set),
          cases_goal_vars(Cases, !Set)
      ;
          GoalExpr = scope(Reason, SubGoal),
          (
              Reason = exist_quant(Vars),
-            svset.insert_list(Vars, !Set)
+            set.insert_list(Vars, !Set)
          ;
              Reason = promise_solutions(Vars, _),
-            svset.insert_list(Vars, !Set)
+            set.insert_list(Vars, !Set)
          ;
              Reason = from_ground_term(Var, _),
-            set.insert(!.Set, Var, !:Set)
+            set.insert(Var, !Set)
          ;
              Reason = require_complete_switch(Var),
-            set.insert(!.Set, Var, !:Set)
+            set.insert(Var, !Set)
          ;
              ( Reason = promise_purity(_)
              ; Reason = require_detism(_)
@@ -610,7 +609,7 @@
          goal_vars_2(SubGoal, !Set)
      ;
          GoalExpr = if_then_else(Vars, Cond, Then, Else),
-        svset.insert_list(Vars, !Set),
+        set.insert_list(Vars, !Set),
          goal_vars_2(Cond, !Set),
          goal_vars_2(Then, !Set),
          goal_vars_2(Else, !Set)
@@ -618,24 +617,24 @@
          GoalExpr = call_foreign_proc(_, _, _, Args, ExtraArgs, _, _),
          ArgVars = list.map(foreign_arg_var, Args),
          ExtraVars = list.map(foreign_arg_var, ExtraArgs),
-        svset.insert_list(ArgVars, !Set),
-        svset.insert_list(ExtraVars, !Set)
+        set.insert_list(ArgVars, !Set),
+        set.insert_list(ExtraVars, !Set)
      ;
          GoalExpr = shorthand(Shorthand),
          (
              Shorthand = atomic_goal(_, Outer, Inner, MaybeOutputVars,
                  MainGoal, OrElseGoals, _),
              Outer = atomic_interface_vars(OuterDI, OuterUO),
-            svset.insert(OuterDI, !Set),
-            svset.insert(OuterUO, !Set),
+            set.insert(OuterDI, !Set),
+            set.insert(OuterUO, !Set),
              Inner = atomic_interface_vars(InnerDI, InnerUO),
-            svset.insert(InnerDI, !Set),
-            svset.insert(InnerUO, !Set),
+            set.insert(InnerDI, !Set),
+            set.insert(InnerUO, !Set),
              (
                  MaybeOutputVars = no
              ;
                  MaybeOutputVars = yes(OutputVars),
-                svset.insert_list(OutputVars, !Set)
+                set.insert_list(OutputVars, !Set)
              ),
              goal_vars_2(MainGoal, !Set),
              goals_goal_vars(OrElseGoals, !Set)
@@ -668,14 +667,14 @@

  rhs_goal_vars(RHS, !Set) :-
      RHS = rhs_var(X),
-    svset.insert(X, !Set).
+    set.insert(X, !Set).
  rhs_goal_vars(RHS, !Set) :-
      RHS = rhs_functor(_Functor, _, ArgVars),
-    svset.insert_list(ArgVars, !Set).
+    set.insert_list(ArgVars, !Set).
  rhs_goal_vars(RHS, !Set) :-
      RHS = rhs_lambda_goal(_, _, _, _, NonLocals, LambdaVars, _, _, Goal),
-    svset.insert_list(NonLocals, !Set),
-    svset.insert_list(LambdaVars, !Set),
+    set.insert_list(NonLocals, !Set),
+    set.insert_list(LambdaVars, !Set),
      goal_vars_2(Goal, !Set).

  generic_call_vars(higher_order(Var, _, _, _), [Var]).
@@ -1201,7 +1200,7 @@
      ;
          GoalExpr = plain_call(PredId, ProcId, _, _, _, _),
          ( list.member(proc(PredId, ProcId), PredProcIds) ->
-            svset.insert(proc(PredId, ProcId), !CalledSet)
+            set.insert(proc(PredId, ProcId), !CalledSet)
          ;
              true
          )
@@ -1382,7 +1381,7 @@
      % of the entire conjunction.
      CaseGoal = hlds_goal(_, CaseGoalInfo),
      CaseNonLocals0 = goal_info_get_nonlocals(CaseGoalInfo),
-    set.insert(CaseNonLocals0, Var, CaseNonLocals),
+    set.insert(Var, CaseNonLocals0, CaseNonLocals),
      CaseInstMapDelta = goal_info_get_instmap_delta(CaseGoalInfo),
      instmap_delta_apply_instmap_delta(ExtraInstMapDelta, CaseInstMapDelta,
          test_size, InstMapDelta),
Index: compiler/graph_colour.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/graph_colour.m,v
retrieving revision 1.20
diff -u -r1.20 graph_colour.m
--- compiler/graph_colour.m	15 Dec 2010 06:29:36 -0000	1.20
+++ compiler/graph_colour.m	5 May 2011 11:21:16 -0000
@@ -38,11 +38,11 @@

  %-----------------------------------------------------------------------------%

-group_elements(Constraints, Colours) :-
-    set.power_union(Constraints, AllVars),
+group_elements(!.Constraints, Colours) :-
+    set.power_union(!.Constraints, AllVars),
      set.init(EmptySet),
-    set.delete(Constraints, EmptySet, Constraints1),
-    set.to_sorted_list(Constraints1, ConstraintList),
+    set.delete(EmptySet, !Constraints),
+    set.to_sorted_list(!.Constraints, ConstraintList),
      find_all_colours(ConstraintList, AllVars, ColourList),
      set.list_to_set(ColourList, Colours).

@@ -110,7 +110,7 @@
                  next_colour(RestVars, NotContaining, ResidueSets, SameColour0),

                  % Add this variable to the variables of the current colour.
-                set.insert(SameColour0, Var, SameColour)
+                set.insert(Var, SameColour0, SameColour)
              )
          ;
              NotContaining = [],
@@ -150,7 +150,7 @@
  divide_constraints(Var, [S | Ss], C, NC, !Vars) :-
      divide_constraints(Var, Ss, C0, NC0, !Vars),
      ( set.member(Var, S) ->
-        set.delete(S, Var, T),
+        set.delete(Var, S, T),
          ( set.empty(T) ->
              C = C0
          ;
@@ -171,7 +171,7 @@
  :- pred choose_var(set(T)::in, T::out, set(T)::out) is det.

  choose_var(Vars0, Var, Vars) :-
-    ( set.remove_least(Vars0, VarPrime, VarsPrime) ->
+    ( set.remove_least(VarPrime, Vars0, VarsPrime) ->
          Var = VarPrime,
          Vars = VarsPrime
      ;
Index: compiler/handle_options.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/handle_options.m,v
retrieving revision 1.363
diff -u -r1.363 handle_options.m
--- compiler/handle_options.m	3 May 2011 04:34:54 -0000	1.363
+++ compiler/handle_options.m	5 May 2011 11:21:38 -0000
@@ -2594,7 +2594,7 @@

          % Check that the component isn't mentioned more than once.
          \+ set.member(Comp, CompSet0),
-        set.insert(CompSet0, Comp, CompSet),
+        set.insert(Comp, CompSet0, CompSet),
          add_option_list(CompOpts, Opts0, Opts1),

          % XXX Here the behaviour matches what used to happen and that is
Index: compiler/headvar_names.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/headvar_names.m,v
retrieving revision 1.11
diff -u -r1.11 headvar_names.m
--- compiler/headvar_names.m	5 May 2011 03:58:54 -0000	1.11
+++ compiler/headvar_names.m	5 May 2011 13:41:11 -0000
@@ -45,7 +45,6 @@
  :- import_module require.
  :- import_module set.
  :- import_module varset.
-:- import_module svset.

  maybe_improve_headvar_names(Globals, !PredInfo) :-
      globals.lookup_bool_option(Globals, make_optimization_interface, MakeOpt),
@@ -221,7 +220,7 @@
  find_headvar_names_in_goal(VarSet, HeadVars, Goal, !VarNameInfoMap,
          !VarsInMap) :-
      ( goal_is_headvar_unification(HeadVars, Goal, HeadVar, MaybeOtherVar) ->
-        svset.insert(HeadVar, !VarsInMap),
+        set.insert(HeadVar, !VarsInMap),
          (
              MaybeOtherVar = no,
              ( map.search(!.VarNameInfoMap, HeadVar, VarNameInfo0) ->
@@ -237,7 +236,7 @@
              ( varset.search_name(VarSet, OtherVar, OtherVarName) ->
                  ( map.search(!.VarNameInfoMap, HeadVar, VarNameInfo0) ->
                      VarNameInfo0 = var_name_info(UnifiedFunctor, VarNames0),
-                    set.insert(VarNames0, OtherVarName, VarNames),
+                    set.insert(OtherVarName, VarNames0, VarNames),
                      VarNameInfo = var_name_info(UnifiedFunctor, VarNames),
                      map.det_update(HeadVar, VarNameInfo, !VarNameInfoMap)
                  ;
Index: compiler/higher_order.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/higher_order.m,v
retrieving revision 1.192
diff -u -r1.192 higher_order.m
--- compiler/higher_order.m	5 May 2011 07:11:50 -0000	1.192
+++ compiler/higher_order.m	5 May 2011 13:06:38 -0000
@@ -81,7 +81,6 @@
  :- import_module require.
  :- import_module set.
  :- import_module string.
-:- import_module svset.
  :- import_module term.
  :- import_module varset.

@@ -1468,7 +1467,7 @@
                  CanRequest = can_request,
                  Requests0 = !.Info ^ hoi_global_info ^ hogi_requests,
                  Changed0 = !.Info ^ hoi_changed,
-                set.insert(Requests0, Request, Requests),
+                set.insert(Request, Requests0, Requests),
                  update_changed_status(Changed0, ho_request, Changed),
                  !Info ^ hoi_global_info ^ hogi_requests := Requests,
                  !Info ^ hoi_changed := Changed
@@ -2300,7 +2299,7 @@
          !Info ^ hoi_proc_info := ProcInfo2
      ;
          MaybeResult = yes(ComparisonResult),
-        set.insert(NonLocals0, ComparisonResult, NonLocals),
+        set.insert(ComparisonResult, NonLocals0, NonLocals),
          InstMapDelta = instmap_delta_bind_var(ComparisonResult),
          Detism = detism_det,
          % Build a new call with the unwrapped arguments.
@@ -2558,7 +2557,7 @@
          !IO) :-
      Request = ho_request(CallingPredProcId, CalledPredProcId, _HOArgs,
          _CallArgs, _, _CallerArgTypes, _, _, _, _),
-    set.insert(!.PredsToFix, CallingPredProcId, !:PredsToFix),
+    set.insert(CallingPredProcId, !PredsToFix),
      ( map.search(!.Info ^ hogi_new_preds, CalledPredProcId, SpecVersions0) ->
          (
              % Check that we aren't redoing the same pred.
@@ -2597,7 +2596,7 @@
                  Request, Version, _)
          )
      ->
-        svset.insert(CallingPredProcId, !PredsToFix)
+        set.insert(CallingPredProcId, !PredsToFix)
      ;
          true
      ).
@@ -2721,7 +2720,7 @@
  add_new_pred(CalledPredProcId, NewPred, !Info) :-
      NewPreds0 = !.Info ^ hogi_new_preds,
      ( map.search(NewPreds0, CalledPredProcId, SpecVersions0) ->
-        set.insert(SpecVersions0, NewPred, SpecVersions),
+        set.insert(NewPred, SpecVersions0, SpecVersions),
          map.det_update(CalledPredProcId, SpecVersions, NewPreds0, NewPreds)
      ;
          set.singleton_set(SpecVersions, NewPred),
Index: compiler/hlds_data.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/hlds_data.m,v
retrieving revision 1.135
diff -u -r1.135 hlds_data.m
--- compiler/hlds_data.m	5 May 2011 06:39:35 -0000	1.135
+++ compiler/hlds_data.m	5 May 2011 11:04:26 -0000
@@ -1448,7 +1448,7 @@
      list.length(Args, Arity),
      ClassId = class_id(Name, Arity),
      ( map.search(!.Redundant, ClassId, Constraints0) ->
-        set.insert(Constraints0, Constraint, Constraints)
+        set.insert(Constraint, Constraints0, Constraints)
      ;
          Constraints = set.make_singleton_set(Constraint)
      ),
Index: compiler/hlds_goal.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/hlds_goal.m,v
retrieving revision 1.224
diff -u -r1.224 hlds_goal.m
--- compiler/hlds_goal.m	5 May 2011 03:58:54 -0000	1.224
+++ compiler/hlds_goal.m	5 May 2011 11:05:11 -0000
@@ -2413,12 +2413,12 @@

  goal_info_add_feature(Feature, !GoalInfo) :-
      Features0 = goal_info_get_features(!.GoalInfo),
-    set.insert(Features0, Feature, Features),
+    set.insert(Feature, Features0, Features),
      goal_info_set_features(Features, !GoalInfo).

  goal_info_remove_feature(Feature, !GoalInfo) :-
      Features0 = goal_info_get_features(!.GoalInfo),
-    ( set.remove(Features0, Feature, Features) ->
+    ( set.remove(Feature, Features0, Features) ->
          goal_info_set_features(Features, !GoalInfo)
      ;
          % !.GoalInfo did not have Feature, so there is no need to allocate
Index: compiler/hlds_module.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/hlds_module.m,v
retrieving revision 1.170
diff -u -r1.170 hlds_module.m
--- compiler/hlds_module.m	3 May 2011 04:34:54 -0000	1.170
+++ compiler/hlds_module.m	5 May 2011 11:06:39 -0000
@@ -1146,7 +1146,7 @@
      !MI ^ mi_sub_info ^ msi_model_non_pragma_counter := NewVal.
  module_add_imported_module_specifiers(IStat, AddedModuleSpecifiers, !MI) :-
      ImportSpecifiers0 = !.MI ^ mi_sub_info ^ msi_imported_module_specifiers,
-    set.insert_list(ImportSpecifiers0, AddedModuleSpecifiers,
+    set.insert_list(AddedModuleSpecifiers, ImportSpecifiers0,
          ImportSpecifiers),
      !MI ^ mi_sub_info ^ msi_imported_module_specifiers := ImportSpecifiers,

@@ -1155,7 +1155,7 @@
          Exported = yes,
          InterfaceSpecifiers0 =
              !.MI ^ mi_sub_info ^ msi_interface_module_specifiers,
-        set.insert_list(InterfaceSpecifiers0, AddedModuleSpecifiers,
+        set.insert_list(AddedModuleSpecifiers, InterfaceSpecifiers0,
              InterfaceSpecifiers),
          !MI ^ mi_sub_info ^ msi_interface_module_specifiers :=
              InterfaceSpecifiers
@@ -1165,7 +1165,7 @@

  module_add_indirectly_imported_module_specifiers(AddedModules, !MI) :-
      Modules0 = !.MI ^ mi_sub_info ^ msi_indirectly_imported_module_specifiers,
-    set.insert_list(Modules0, AddedModules, Modules),
+    set.insert_list(AddedModules, Modules0, Modules),
      !MI ^ mi_sub_info ^ msi_indirectly_imported_module_specifiers := Modules.

  module_info_set_type_spec_info(NewVal, !MI) :-
Index: compiler/hlds_out_mode.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/hlds_out_mode.m,v
retrieving revision 1.2
diff -u -r1.2 hlds_out_mode.m
--- compiler/hlds_out_mode.m	15 Dec 2010 06:29:38 -0000	1.2
+++ compiler/hlds_out_mode.m	5 May 2011 11:08:06 -0000
@@ -436,7 +436,7 @@
          mercury_format_inst_name(InstName, ExpandedInstInfo, !S)
      ;
          inst_lookup(ExpandedInstInfo ^ eii_module_info, InstName, Inst),
-        set.insert(ExpandedInstInfo ^ eii_expansions, InstName, Expansions),
+        set.insert(InstName, ExpandedInstInfo ^ eii_expansions, Expansions),
          mercury_format_inst(Inst,
              ExpandedInstInfo ^ eii_expansions := Expansions, !S)
      ).
Index: compiler/hlds_pred.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/hlds_pred.m,v
retrieving revision 1.269
diff -u -r1.269 hlds_pred.m
--- compiler/hlds_pred.m	5 May 2011 03:58:54 -0000	1.269
+++ compiler/hlds_pred.m	5 May 2011 11:09:23 -0000
@@ -1186,7 +1186,7 @@
          NonLocals = goal_info_get_nonlocals(GoalInfo),
          goal_util.extra_nonlocal_typeinfos(RttiVarMaps, VarTypes0,
              ExistQVars, NonLocals, ExtraTypeInfos0),
-        set.delete_list(ExtraTypeInfos0, ArgVars0, ExtraTypeInfos1),
+        set.delete_list(ArgVars0, ExtraTypeInfos0, ExtraTypeInfos1),
          set.to_sorted_list(ExtraTypeInfos1, ExtraTypeInfos),
          list.append(ExtraTypeInfos, ArgVars0, ArgVars)
      ;
@@ -1206,7 +1206,7 @@

      % Remove unneeded variables from the vartypes and varset.
      goal_util.goal_vars(Goal0, GoalVars0),
-    set.insert_list(GoalVars0, ArgVars, GoalVars),
+    set.insert_list(ArgVars, GoalVars0, GoalVars),
      map.select(VarTypes0, GoalVars, VarTypes),
      varset.select(GoalVars, VarSet0, VarSet),

Index: compiler/inlining.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/inlining.m,v
retrieving revision 1.171
diff -u -r1.171 inlining.m
--- compiler/inlining.m	3 May 2011 04:34:55 -0000	1.171
+++ compiler/inlining.m	5 May 2011 13:41:17 -0000
@@ -172,7 +172,6 @@
  :- import_module pair.
  :- import_module require.
  :- import_module set.
-:- import_module svset.
  :- import_module term.
  :- import_module varset.

@@ -376,7 +375,7 @@
      set(pred_proc_id)::in, set(pred_proc_id)::out) is det.

  mark_proc_as_inlined(proc(PredId, ProcId), ModuleInfo, !InlinedProcs) :-
-    svset.insert(proc(PredId, ProcId), !InlinedProcs),
+    set.insert(proc(PredId, ProcId), !InlinedProcs),
      module_info_pred_info(ModuleInfo, PredId, PredInfo),
      ( pred_info_requested_inlining(PredInfo) ->
          true
Index: compiler/inst_match.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/inst_match.m,v
retrieving revision 1.92
diff -u -r1.92 inst_match.m
--- compiler/inst_match.m	5 May 2011 06:39:35 -0000	1.92
+++ compiler/inst_match.m	5 May 2011 13:42:02 -0000
@@ -332,7 +332,6 @@
  :- import_module require.
  :- import_module set.
  :- import_module set_tree234.
-:- import_module svset.
  :- import_module term.

  %-----------------------------------------------------------------------------%
@@ -1430,7 +1429,7 @@
      ( set.member(Inst, !.Expansions) ->
          true
      ;
-        svset.insert(Inst, !Expansions),
+        set.insert(Inst, !Expansions),
          inst_lookup(ModuleInfo, InstName, Inst2),
          inst_is_ground_or_any_2(ModuleInfo, Inst2, !Expansions)
      ).
@@ -1464,7 +1463,7 @@
      ( set.member(Inst, !.Expansions) ->
          true
      ;
-        svset.insert(Inst, !Expansions),
+        set.insert(Inst, !Expansions),
          inst_lookup(ModuleInfo, InstName, Inst2),
          inst_is_unique_2(ModuleInfo, Inst2, !Expansions)
      ).
@@ -1502,7 +1501,7 @@
      ( set.member(Inst, !.Expansions) ->
          true
      ;
-        svset.insert(Inst, !Expansions),
+        set.insert(Inst, !Expansions),
          inst_lookup(ModuleInfo, InstName, Inst2),
          inst_is_mostly_unique_2(ModuleInfo, Inst2, !Expansions)
      ).
@@ -1536,7 +1535,7 @@
      ( set.member(Inst, !.Expansions) ->
          true
      ;
-        svset.insert(Inst, !Expansions),
+        set.insert(Inst, !Expansions),
          inst_lookup(ModuleInfo, InstName, Inst2),
          inst_is_not_partly_unique_2(ModuleInfo, Inst2, !Expansions)
      ).
@@ -1579,7 +1578,7 @@
      ( set.member(Inst, !.Expansions) ->
          true
      ;
-        svset.insert(Inst, !Expansions),
+        set.insert(Inst, !Expansions),
          inst_lookup(ModuleInfo, InstName, Inst2),
          inst_is_not_fully_unique_2(ModuleInfo, Inst2, !Expansions)
      ).
@@ -1857,7 +1856,7 @@
              Result = no
          ;
              inst_lookup(ModuleInfo, InstName1, Inst1),
-            svset.insert(InstName1, !Expansions),
+            set.insert(InstName1, !Expansions),
              inst_contains_instname_2(Inst1, ModuleInfo, InstName, Result,
                  !Expansions)
          )
Index: compiler/inst_util.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/inst_util.m,v
retrieving revision 1.62
diff -u -r1.62 inst_util.m
--- compiler/inst_util.m	3 May 2011 04:34:55 -0000	1.62
+++ compiler/inst_util.m	5 May 2011 13:42:23 -0000
@@ -163,7 +163,6 @@
  :- import_module pair.
  :- import_module require.
  :- import_module set.
-:- import_module svset.

  %-----------------------------------------------------------------------------%

@@ -1670,7 +1669,7 @@
      ( set.member(InstName, !.Expansions) ->
          Uniq = UniqB
      ;
-        svset.insert(InstName, !Expansions),
+        set.insert(InstName, !Expansions),
          inst_lookup(ModuleInfo, InstName, Inst),
          merge_inst_uniq(Inst, UniqB, ModuleInfo, !Expansions, Uniq)
      ).
@@ -1783,7 +1782,7 @@
  inst_contains_nonstandard_func_mode_2(ModuleInfo, Inst, Expansions0) :-
      Inst = defined_inst(InstName),
      \+ set.member(Inst, Expansions0),
-    set.insert(Expansions0, Inst, Expansions1),
+    set.insert(Inst, Expansions0, Expansions1),
      inst_lookup(ModuleInfo, InstName, Inst2),
      inst_contains_nonstandard_func_mode_2(ModuleInfo, Inst2, Expansions1).

Index: compiler/instmap.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/instmap.m,v
retrieving revision 1.71
diff -u -r1.71 instmap.m
--- compiler/instmap.m	3 May 2011 04:34:55 -0000	1.71
+++ compiler/instmap.m	5 May 2011 11:12:14 -0000
@@ -485,11 +485,11 @@
  :- pred instmap_bound_vars_2(module_info::in, prog_var::in, mer_inst::in,
      set(prog_var)::in, set(prog_var)::out) is det.

-instmap_bound_vars_2(ModuleInfo, Var, Inst, BoundVars0, BoundVars) :-
+instmap_bound_vars_2(ModuleInfo, Var, Inst, !BoundVars) :-
      ( inst_is_bound(ModuleInfo, Inst) ->
-        set.insert(BoundVars0, Var, BoundVars)
+        set.insert(Var, !BoundVars)
      ;
-        BoundVars = BoundVars0
+        true
      ).

  instmap_delta_changed_vars(unreachable, EmptySet) :-
@@ -523,7 +523,7 @@
      ( inst_matches_final_typed(InitialInst, FinalInst, Type, ModuleInfo) ->
          ChangedVars = ChangedVars0
      ;
-        set.insert(ChangedVars0, VarB, ChangedVars)
+        set.insert(VarB, ChangedVars0, ChangedVars)
      ).

  %-----------------------------------------------------------------------------%
@@ -1283,7 +1283,7 @@
      map.keys(InstMappingA, VarsInA),
      map.keys(InstMappingB, VarsInB),
      set.sorted_list_to_set(VarsInA, SetofVarsInA),
-    set.insert_list(SetofVarsInA, VarsInB, SetofVars0),
+    set.insert_list(VarsInB, SetofVarsInA, SetofVars0),
      set.intersect(SetofVars0, NonLocals, SetofVars),
      set.to_sorted_list(SetofVars, ListofVars),
      merge_instmapping_delta_2(ListofVars, InstMap, VarTypes,
@@ -1361,7 +1361,7 @@
      map.keys(InstMappingA, VarsInA),
      map.keys(InstMappingB, VarsInB),
      set.sorted_list_to_set(VarsInA, SetofVarsInA),
-    set.insert_list(SetofVarsInA, VarsInB, SetofVars0),
+    set.insert_list(VarsInB, SetofVarsInA, SetofVars0),
      set.intersect(SetofVars0, NonLocals, SetofVars),
      set.to_sorted_list(SetofVars, ListofVars),
      unify_instmapping_delta_2(ListofVars, InstMap, InstMappingA, InstMappingB,
Index: compiler/intermod.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/intermod.m,v
retrieving revision 1.261
diff -u -r1.261 intermod.m
--- compiler/intermod.m	5 May 2011 03:58:54 -0000	1.261
+++ compiler/intermod.m	5 May 2011 13:07:48 -0000
@@ -272,7 +272,7 @@
              ;
                  true
              ),
-            set.insert(Preds0, PredId, Preds),
+            set.insert(PredId, Preds0, Preds),
              intermod_info_set_preds(Preds, !Info),
              intermod_info_set_module_info(ModuleInfo, !Info)
          ;
@@ -730,7 +730,7 @@
      ->
          DoWrite = yes,
          intermod_info_get_pred_decls(!.Info, PredDecls0),
-        set.insert(PredDecls0, PredId, PredDecls),
+        set.insert(PredId, PredDecls0, PredDecls),
          intermod_info_set_pred_decls(PredDecls, !Info)
      ;
          ( Status = status_imported(_)
@@ -742,7 +742,7 @@
          DoWrite = yes,
          PredModule = pred_info_module(PredInfo),
          intermod_info_get_modules(!.Info, Modules0),
-        set.insert(Modules0, PredModule, Modules),
+        set.insert(PredModule, Modules0, Modules),
          intermod_info_set_modules(Modules, !Info)
      ;
          unexpected(this_file, "add_proc: unexpected status")
Index: compiler/interval.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/interval.m,v
retrieving revision 1.49
diff -u -r1.49 interval.m
--- compiler/interval.m	5 May 2011 03:58:54 -0000	1.49
+++ compiler/interval.m	5 May 2011 13:42:30 -0000
@@ -197,7 +197,6 @@
  :- import_module assoc_list.
  :- import_module pair.
  :- import_module require.
-:- import_module svset.
  :- import_module term.
  :- import_module varset.

@@ -622,7 +621,7 @@
      record_interval_succ(CondTailId, ThenStartId, !IntervalInfo),
      set_cur_interval(CondTailId, !IntervalInfo),
      get_open_intervals(!.IntervalInfo, OpenIntervals0),
-    svset.insert(CondTailId, OpenIntervals0, OpenIntervals),
+    set.insert(CondTailId, OpenIntervals0, OpenIntervals),
      set_open_intervals(OpenIntervals, !IntervalInfo).

  :- pred leave_branch_start(branch_construct::in, anchor::in, interval_id::in,
@@ -785,7 +784,7 @@
  record_interval_vars(Id, NewVars, !IntervalInfo) :-
      VarsMap0 = !.IntervalInfo ^ ii_interval_vars,
      ( map.search(VarsMap0, Id, Vars0) ->
-        svset.insert_list(NewVars, Vars0, Vars),
+        set.insert_list(NewVars, Vars0, Vars),
          map.det_update(Id, Vars, VarsMap0, VarsMap)
      ;
          set.list_to_set(NewVars, Vars),
@@ -833,7 +832,7 @@

  require_access(Vars, !IntervalInfo) :-
      AccessedLater0 = !.IntervalInfo ^ ii_accessed_later,
-    svset.insert_list(Vars, AccessedLater0, AccessedLater),
+    set.insert_list(Vars, AccessedLater0, AccessedLater),
      !IntervalInfo ^ ii_accessed_later := AccessedLater.

  :- pred record_branch_resume(goal_id::in, resume_save_status::in,
@@ -850,7 +849,7 @@

  record_model_non_anchor(Anchor, !IntervalInfo) :-
      ModelNonAnchors0 = !.IntervalInfo ^ ii_model_non_anchors,
-    svset.insert(Anchor, ModelNonAnchors0, ModelNonAnchors),
+    set.insert(Anchor, ModelNonAnchors0, ModelNonAnchors),
      !IntervalInfo ^ ii_model_non_anchors := ModelNonAnchors.

  %-----------------------------------------------------------------------------%
Index: compiler/ite_gen.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/ite_gen.m,v
retrieving revision 1.111
diff -u -r1.111 ite_gen.m
--- compiler/ite_gen.m	30 Dec 2010 11:17:55 -0000	1.111
+++ compiler/ite_gen.m	5 May 2011 11:28:57 -0000
@@ -750,7 +750,7 @@
          pred_info_name(PredInfo) = remove_region_pred_name,
          Args = [RegionVar]
      ->
-        set.insert(!.Removed, RegionVar, !:Removed),
+        set.insert(RegionVar, !Removed),
          find_regions_removed_at_start_of_goals(Goals, ModuleInfo, !Removed)
      ;
          true
Index: compiler/labelopt.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/labelopt.m,v
retrieving revision 1.37
diff -u -r1.37 labelopt.m
--- compiler/labelopt.m	30 Dec 2010 11:17:55 -0000	1.37
+++ compiler/labelopt.m	5 May 2011 13:42:37 -0000
@@ -47,7 +47,6 @@
  :- import_module ll_backend.opt_util.

  :- import_module maybe.
-:- import_module svset.

  %-----------------------------------------------------------------------------%

@@ -69,7 +68,7 @@
  build_useset([Instr | Instructions], !Useset) :-
      Instr = llds_instr(Uinstr, _Comment),
      opt_util.instr_labels(Uinstr, Labels, _CodeAddresses),
-    svset.insert_list(Labels, !Useset),
+    set.insert_list(Labels, !Useset),
      build_useset(Instructions, !Useset).

  %-----------------------------------------------------------------------------%
Index: compiler/lambda.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/lambda.m,v
retrieving revision 1.148
diff -u -r1.148 lambda.m
--- compiler/lambda.m	3 May 2011 04:34:55 -0000	1.148
+++ compiler/lambda.m	5 May 2011 13:09:27 -0000
@@ -373,7 +373,7 @@
      ExistQVars = [],
      LambdaGoal = hlds_goal(_, LambdaGoalInfo),
      LambdaGoalNonLocals = goal_info_get_nonlocals(LambdaGoalInfo),
-    set.insert_list(LambdaGoalNonLocals, Vars, LambdaNonLocals),
+    set.insert_list(Vars, LambdaGoalNonLocals, LambdaNonLocals),
      goal_util.extra_nonlocal_typeinfos(RttiVarMaps, VarTypes, ExistQVars,
          LambdaNonLocals, ExtraTypeInfos),
      OrigVars = OrigNonLocals0,
@@ -389,7 +389,7 @@
          unexpected(this_file, "expand_lambda: unexpected unification")
      ),

-    set.delete_list(LambdaGoalNonLocals, Vars, NonLocals1),
+    set.delete_list(Vars, LambdaGoalNonLocals, NonLocals1),

      % We need all the typeinfos, including the ones that are not used,
      % for the layout structure describing the closure.
Index: compiler/live_vars.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/live_vars.m,v
retrieving revision 1.143
diff -u -r1.143 live_vars.m
--- compiler/live_vars.m	30 Dec 2010 11:17:55 -0000	1.143
+++ compiler/live_vars.m	5 May 2011 11:29:25 -0000
@@ -338,7 +338,7 @@
              % The scope does not contain any calls, resume points or parallel
              % conjunctions, so there are no updates to !StackAlloc,
              % !NondetLiveness, or !ParStackVars.
-            set.insert(!.Liveness, TermVar, !:Liveness)
+            set.insert(TermVar, !Liveness)
          ;
              NondetLiveness0 = !.NondetLiveness,
              build_live_sets_in_goal(SubGoal0, SubGoal, ResumeVars0, AllocData,
Index: compiler/livemap.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/livemap.m,v
retrieving revision 1.97
diff -u -r1.97 livemap.m
--- compiler/livemap.m	3 May 2011 04:34:55 -0000	1.97
+++ compiler/livemap.m	5 May 2011 13:42:45 -0000
@@ -46,7 +46,6 @@
  :- import_module bool.
  :- import_module require.
  :- import_module string.
-:- import_module svset.

  %-----------------------------------------------------------------------------%
  %-----------------------------------------------------------------------------%
@@ -155,7 +154,7 @@
          % appears on the right hand side as well as the left, then we
          % want make_live to put it back into the liveval set.

-        svset.delete(Lval, !Livevals),
+        set.delete(Lval, !Livevals),
          opt_util.lval_access_rvals(Lval, Rvals),
          livemap.make_live_in_rvals([Rval | Rvals], !Livevals)
      ;
@@ -200,7 +199,7 @@
          livemap_special_code_addr(CodeAddr, MaybeSpecial),
          (
              MaybeSpecial = yes(Special),
-            set.insert(!.Livevals, Special, !:Livevals)
+            set.insert(Special, !Livevals)
          ;
              MaybeSpecial = no
          )
@@ -234,13 +233,13 @@
          livemap_special_code_addr(CodeAddr, MaybeSpecial),
          (
              MaybeSpecial = yes(Special),
-            set.insert(!.Livevals, Special, !:Livevals)
+            set.insert(Special, !Livevals)
          ;
              MaybeSpecial = no
          )
      ;
          Uinstr0 = save_maxfr(Lval),
-        svset.delete(Lval, !Livevals),
+        set.delete(Lval, !Livevals),
          opt_util.lval_access_rvals(Lval, Rvals),
          livemap.make_live_in_rvals(Rvals, !Livevals)
      ;
@@ -257,7 +256,7 @@
          % to lval, but the two should never have any variables in
          % common. This is why doing the deletion first works.

-        svset.delete(Lval, !Livevals),
+        set.delete(Lval, !Livevals),
          opt_util.lval_access_rvals(Lval, Rvals),
          livemap.make_live_in_rvals(Rvals, !Livevals),
          livemap.make_live_in_rval(SizeRval, !Livevals),
@@ -276,14 +275,14 @@
                  MaybeFlagLval = no
              ;
                  MaybeFlagLval = yes(FlagLval),
-                svset.delete(FlagLval, !Livevals),
+                set.delete(FlagLval, !Livevals),
                  opt_util.lval_access_rvals(FlagLval, FlagRvals),
                  livemap.make_live_in_rvals(FlagRvals, !Livevals)
              )
          )
      ;
          Uinstr0 = mark_hp(Lval),
-        svset.delete(Lval, !Livevals),
+        set.delete(Lval, !Livevals),
          opt_util.lval_access_rvals(Lval, Rvals),
          livemap.make_live_in_rvals(Rvals, !Livevals)
      ;
@@ -317,7 +316,7 @@
          % as live would be redundant.
      ;
          Uinstr0 = store_ticket(Lval),
-        svset.delete(Lval, !Livevals),
+        set.delete(Lval, !Livevals),
          opt_util.lval_access_rvals(Lval, Rvals),
          livemap.make_live_in_rvals(Rvals, !Livevals)
      ;
@@ -329,7 +328,7 @@
          Uinstr0 = prune_ticket
      ;
          Uinstr0 = mark_ticket_stack(Lval),
-        svset.delete(Lval, !Livevals),
+        set.delete(Lval, !Livevals),
          opt_util.lval_access_rvals(Lval, Rvals),
          livemap.make_live_in_rvals(Rvals, !Livevals)
      ;
@@ -501,7 +500,7 @@
      ( Lval = field(_, _, _) ->
          true
      ;
-        set.insert(!.Live, Lval, !:Live)
+        set.insert(Lval, !Live)
      ),
      opt_util.lval_access_rvals(Lval, AccessRvals),
      make_live_in_rvals(AccessRvals, !Live).
@@ -577,7 +576,7 @@
      ( Live = field(_, _, _) ->
          true
      ;
-        set.insert(!.Livevals, Live, !:Livevals)
+        set.insert(Live, !Livevals)
      ).

  %-----------------------------------------------------------------------------%
Index: compiler/liveness.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/liveness.m,v
retrieving revision 1.178
diff -u -r1.178 liveness.m
--- compiler/liveness.m	30 Dec 2010 11:17:55 -0000	1.178
+++ compiler/liveness.m	5 May 2011 13:43:04 -0000
@@ -212,7 +212,6 @@
  :- import_module pair.
  :- import_module require.
  :- import_module string.
-:- import_module svset.
  :- import_module term.
  :- import_module varset.

@@ -587,8 +586,8 @@
          Unification = construct(LHSVar, _ConsId, RHSVars, _ArgModes,
              construct_statically, cell_is_shared, no_construct_sub_info)
      ->
-        ( set.remove_list(!.LocalLiveVars, RHSVars, !:LocalLiveVars) ->
-            set.insert(!.LocalLiveVars, LHSVar, !:LocalLiveVars),
+        ( set.remove_list(RHSVars, !LocalLiveVars) ->
+            set.insert(LHSVar, !LocalLiveVars),
              PreBirths = set.make_singleton_set(LHSVar),
              set.init(PostBirths),
              set.init(PreDeaths),
@@ -1745,7 +1744,7 @@
  initial_liveness_2([], [], [], _ModuleInfo, !Liveness).
  initial_liveness_2([V | Vs], [M | Ms], [T | Ts], ModuleInfo, !Liveness) :-
      ( mode_to_arg_mode(ModuleInfo, M, T, top_in) ->
-        svset.insert(V, !Liveness)
+        set.insert(V, !Liveness)
      ;
          true
      ),
@@ -1817,7 +1816,7 @@
          ModuleInfo = LiveInfo ^ li_module_info,
          mode_to_arg_mode(ModuleInfo, (free -> Inst), Type, top_out)
      ->
-        svset.insert(Var, !ValueVars)
+        set.insert(Var, !ValueVars)
      ;
          true
      ),
Index: compiler/llds_out_file.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/llds_out_file.m,v
retrieving revision 1.5
diff -u -r1.5 llds_out_file.m
--- compiler/llds_out_file.m	3 May 2011 04:34:55 -0000	1.5
+++ compiler/llds_out_file.m	5 May 2011 11:31:31 -0000
@@ -745,7 +745,7 @@
          ( set.member(Code, !.AlreadyDone) ->
              true
          ;
-            set.insert(!.AlreadyDone, Code, !:AlreadyDone),
+            set.insert(Code, !AlreadyDone),
              AutoComments = Info ^ lout_auto_comments,
              LineNumbers = Info ^ lout_line_numbers,
              (
Index: compiler/lp.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/lp.m,v
retrieving revision 1.22
diff -u -r1.22 lp.m
--- compiler/lp.m	5 May 2011 03:58:54 -0000	1.22
+++ compiler/lp.m	5 May 2011 13:43:12 -0000
@@ -96,7 +96,6 @@
  :- import_module set.
  :- import_module solutions.
  :- import_module string.
-:- import_module svset.

  %-----------------------------------------------------------------------------%

@@ -208,7 +207,7 @@

  get_vars_from_coeffs_2([], !SetVar).
  get_vars_from_coeffs_2([Var - _ | Coeffs], !SetVar) :-
-    svset.insert(Var, !SetVar),
+    set.insert(Var, !SetVar),
      get_vars_from_coeffs_2(Coeffs, !SetVar).

  %-----------------------------------------------------------------------------%
Index: compiler/lp_rational.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/lp_rational.m,v
retrieving revision 1.17
diff -u -r1.17 lp_rational.m
--- compiler/lp_rational.m	5 May 2011 07:11:50 -0000	1.17
+++ compiler/lp_rational.m	5 May 2011 13:43:25 -0000
@@ -334,7 +334,6 @@
  :- import_module require.
  :- import_module solutions.
  :- import_module string.
-:- import_module svset.

  %-----------------------------------------------------------------------------%
  %
@@ -2268,7 +2267,7 @@

  get_vars_from_terms([], !SetVar).
  get_vars_from_terms([Var - _ | Coeffs], !SetVar) :-
-    svset.insert(Var, !SetVar),
+    set.insert(Var, !SetVar),
      get_vars_from_terms(Coeffs, !SetVar).

  %-----------------------------------------------------------------------------%
Index: compiler/make.dependencies.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/make.dependencies.m,v
retrieving revision 1.59
diff -u -r1.59 make.dependencies.m
--- compiler/make.dependencies.m	30 Dec 2010 11:17:56 -0000	1.59
+++ compiler/make.dependencies.m	5 May 2011 12:32:19 -0000
@@ -253,9 +253,9 @@
  :- pred module_index_set_to_plain_set_2(make_info::in, module_index::in,
      set(module_name)::in, set(module_name)::out) is det.

-module_index_set_to_plain_set_2(Info, ModuleIndex, Set0, Set) :-
+module_index_set_to_plain_set_2(Info, ModuleIndex, !Set) :-
      module_index_to_name(Info, ModuleIndex, ModuleName),
-    set.insert(Set0, ModuleName, Set).
+    set.insert(ModuleName, !Set).

  :- pred dependency_file_to_index(dependency_file::in,
      dependency_file_index::out, make_info::in, make_info::out) is det.
Index: compiler/make_hlds_passes.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/make_hlds_passes.m,v
retrieving revision 1.109
diff -u -r1.109 make_hlds_passes.m
--- compiler/make_hlds_passes.m	5 May 2011 03:58:54 -0000	1.109
+++ compiler/make_hlds_passes.m	5 May 2011 11:14:29 -0000
@@ -2958,7 +2958,7 @@
              Name, Arity, PredIds)
      ->
          module_info_get_stratified_preds(!.ModuleInfo, StratPredIds0),
-        set.insert_list(StratPredIds0, PredIds, StratPredIds),
+        set.insert_list(PredIds, StratPredIds0, StratPredIds),
          module_info_set_stratified_preds(StratPredIds, !ModuleInfo)
      ;
          string.append_list(["`:- pragma ", PragmaName, "' declaration"],
Index: compiler/make_hlds_warn.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/make_hlds_warn.m,v
retrieving revision 1.38
diff -u -r1.38 make_hlds_warn.m
--- compiler/make_hlds_warn.m	29 Dec 2010 04:52:17 -0000	1.38
+++ compiler/make_hlds_warn.m	5 May 2011 11:15:54 -0000
@@ -155,7 +155,7 @@
                  set.init(EmptySet),
                  warn_singletons_goal_vars(Vars, GoalInfo, EmptySet, SubGoalVars,
                      VarSet, PredCallId, !Specs),
-                set.insert_list(QuantVars, Vars, SubQuantVars)
+                set.insert_list(Vars, QuantVars, SubQuantVars)
              ;
                  Vars = [],
                  SubQuantVars = QuantVars
@@ -198,7 +198,7 @@
          ;
              Vars = []
          ),
-        set.insert_list(QuantVars, Vars, CondThenQuantVars),
+        set.insert_list(Vars, QuantVars, CondThenQuantVars),
          warn_singletons_in_goal(Cond, CondThenQuantVars, VarSet, PredCallId,
              ModuleInfo, !Specs),
          warn_singletons_in_goal(Then, CondThenQuantVars, VarSet, PredCallId,
@@ -237,7 +237,7 @@
              ShortHand = atomic_goal(_GoalType, _Outer, Inner,
                  _MaybeOutputVars, MainGoal, OrElseGoals, _OrElseInners),
              Inner = atomic_interface_vars(InnerDI, InnerUO),
-            set.insert_list(QuantVars, [InnerDI, InnerUO], InsideQuantVars),
+            set.insert_list([InnerDI, InnerUO], QuantVars, InsideQuantVars),
              warn_singletons_in_goal(MainGoal, InsideQuantVars, VarSet,
                  PredCallId, ModuleInfo, !Specs),
              warn_singletons_in_goal_list(OrElseGoals, InsideQuantVars, VarSet,
Index: compiler/matching.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/matching.m,v
retrieving revision 1.16
diff -u -r1.16 matching.m
--- compiler/matching.m	3 May 2011 05:12:03 -0000	1.16
+++ compiler/matching.m	5 May 2011 10:32:30 -0000
@@ -624,7 +624,7 @@
      FieldCostsBenefits = field_costs_benefits(FieldVar, _, FieldBenefits),
      set.intersect(FieldBenefits, MarkedBenefits, MarkedFieldBenefits),
      ( set.empty(MarkedFieldBenefits) ->
-        set.insert(ViaCellVars1, FieldVar, ViaCellVars)
+        set.insert(FieldVar, ViaCellVars1, ViaCellVars)
      ; set.equal(MarkedFieldBenefits, FieldBenefits) ->
          ViaCellVars = ViaCellVars1
      ;
Index: compiler/mercury_to_mercury.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/mercury_to_mercury.m,v
retrieving revision 1.347
diff -u -r1.347 mercury_to_mercury.m
--- compiler/mercury_to_mercury.m	8 Apr 2011 07:25:45 -0000	1.347
+++ compiler/mercury_to_mercury.m	5 May 2011 12:37:06 -0000
@@ -1822,12 +1822,12 @@
      InstInfo::in, U::di, U::uo) is det
      <= (output(U), inst_info(InstInfo)).

-mercury_format_constrained_inst_vars(Vars0, Inst, InstInfo, !U) :-
-    ( set.remove_least(Vars0, Var, Vars1) ->
+mercury_format_constrained_inst_vars(!.Vars, Inst, InstInfo, !U) :-
+    ( set.remove_least(Var, !Vars) ->
          add_string("(", !U),
          mercury_format_var(InstInfo ^ instvarset, no, Var, !U),
          add_string(" =< ", !U),
-        mercury_format_constrained_inst_vars(Vars1, Inst, InstInfo, !U),
+        mercury_format_constrained_inst_vars(!.Vars, Inst, InstInfo, !U),
          add_string(")", !U)
      ;
          mercury_format_inst(Inst, InstInfo, !U)
Index: compiler/middle_rec.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/middle_rec.m,v
retrieving revision 1.142
diff -u -r1.142 middle_rec.m
--- compiler/middle_rec.m	25 Mar 2011 03:13:40 -0000	1.142
+++ compiler/middle_rec.m	5 May 2011 11:35:27 -0000
@@ -471,7 +471,7 @@
  add_counter_to_livevals([], _Lval, []).
  add_counter_to_livevals([Instr0 | Instrs0], Lval, [Instr | Instrs]) :-
      ( Instr0 = llds_instr(livevals(Lives0), Comment) ->
-        set.insert(Lives0, Lval, Lives),
+        set.insert(Lval, Lives0, Lives),
          Instr = llds_instr(livevals(Lives), Comment)
      ;
          Instr = Instr0
@@ -632,7 +632,7 @@
  find_used_registers_lval(Lval, !Used) :-
      ( Lval = reg(reg_r, N) ->
          copy(N, N1),
-        set.insert(!.Used, N1, !:Used)
+        set.insert(N1, !Used)
      ; Lval = field(_, Rval, FieldNum) ->
          find_used_registers_rval(Rval, !Used),
          find_used_registers_rval(FieldNum, !Used)
Index: compiler/ml_closure_gen.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/ml_closure_gen.m,v
retrieving revision 1.66
diff -u -r1.66 ml_closure_gen.m
--- compiler/ml_closure_gen.m	30 Dec 2010 11:17:56 -0000	1.66
+++ compiler/ml_closure_gen.m	5 May 2011 12:32:49 -0000
@@ -472,7 +472,7 @@
      term.var_to_int(TVar, TVarNum),
      NextSlot = CurSlot + 1,
      ( TVarNum = CurSlot ->
-        ( set.remove_least(Locns, LeastLocn, _) ->
+        ( set.remove_least(LeastLocn, Locns, _) ->
              Locn = LeastLocn
          ;
              unexpected(this_file, "tvar has empty set of locations")
Index: compiler/ml_gen_info.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/ml_gen_info.m,v
retrieving revision 1.2
diff -u -r1.2 ml_gen_info.m
--- compiler/ml_gen_info.m	3 May 2011 04:34:55 -0000	1.2
+++ compiler/ml_gen_info.m	5 May 2011 12:33:29 -0000
@@ -597,7 +597,7 @@

  ml_gen_info_add_env_var_name(Name, !Info) :-
      ml_gen_info_get_env_var_names(!.Info, EnvVarNames0),
-    set.insert(EnvVarNames0, Name, EnvVarNames),
+    set.insert(Name, EnvVarNames0, EnvVarNames),
      ml_gen_info_set_env_var_names(EnvVarNames, !Info).

  %-----------------------------------------------------------------------------%
Index: compiler/ml_lookup_switch.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/ml_lookup_switch.m,v
retrieving revision 1.8
diff -u -r1.8 ml_lookup_switch.m
--- compiler/ml_lookup_switch.m	3 May 2011 04:34:56 -0000	1.8
+++ compiler/ml_lookup_switch.m	5 May 2011 12:34:29 -0000
@@ -65,7 +65,7 @@

  ml_gen_lookup_switch(SwitchVar, TaggedCases, NonLocals, CodeModel, Context,
          StartVal, EndVal, NeedBitVecCheck, NeedRangeCheck, Statement, !Info) :-
-    set.remove(NonLocals, SwitchVar, OtherNonLocals),
+    set.remove(SwitchVar, NonLocals, OtherNonLocals),
      set.to_sorted_list(OtherNonLocals, OutVars),
      ml_generate_constants_for_lookup_switch(CodeModel, OutVars, OtherNonLocals,
          TaggedCases, map.init, CaseSolnMap, !Info),
Index: compiler/ml_proc_gen.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/ml_proc_gen.m,v
retrieving revision 1.11
diff -u -r1.11 ml_proc_gen.m
--- compiler/ml_proc_gen.m	3 May 2011 04:34:56 -0000	1.11
+++ compiler/ml_proc_gen.m	5 May 2011 12:35:15 -0000
@@ -583,7 +583,7 @@
      Goal = hlds_goal(_, GoalInfo),
      Context = goal_info_get_context(GoalInfo),
      goal_util.goal_vars(Goal, AllVarsSet),
-    set.delete_list(AllVarsSet, HeadVars, LocalVarsSet),
+    set.delete_list(HeadVars, AllVarsSet, LocalVarsSet),
      set.to_sorted_list(LocalVarsSet, LocalVars),
      ml_gen_local_var_decls(VarSet, VarTypes, Context, LocalVars,
          MLDS_LocalVars0, !Info),
Index: compiler/mode_constraints.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/mode_constraints.m,v
retrieving revision 1.62
diff -u -r1.62 mode_constraints.m
--- compiler/mode_constraints.m	3 May 2011 04:34:56 -0000	1.62
+++ compiler/mode_constraints.m	5 May 2011 10:35:33 -0000
@@ -1624,7 +1624,7 @@
                  ), Args, ArgsGi0, !GCInfo),
              ArgsGi = list_to_set(ArgsGi0),
              get_var(LHSVar `at` GoalId, LHSVargi, !GCInfo),
-            ( remove_least(ArgsGi, Arg1gi, ArgsGi1) ->
+            ( set.remove_least(Arg1gi, ArgsGi, ArgsGi1) ->
                  !:Constraint = !.Constraint
                      ^ neq_vars(Arg1gi, LHSVargi)
                      ^ fold(eq_vars(Arg1gi), ArgsGi1)
Index: compiler/modecheck_unify.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/modecheck_unify.m,v
retrieving revision 1.139
diff -u -r1.139 modecheck_unify.m
--- compiler/modecheck_unify.m	5 May 2011 03:58:55 -0000	1.139
+++ compiler/modecheck_unify.m	5 May 2011 10:37:33 -0000
@@ -376,7 +376,7 @@
      % is safe to bind the lambda goal itself.
      Goal0 = hlds_goal(_, GoalInfo0),
      NonLocals0 = goal_info_get_nonlocals(GoalInfo0),
-    set.delete_list(NonLocals0, Vars, NonLocals1),
+    set.delete_list(Vars, NonLocals0, NonLocals1),
      (
          Groundness = ho_ground,
          NonLocals = NonLocals1
Index: compiler/modecheck_util.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/modecheck_util.m,v
retrieving revision 1.5
diff -u -r1.5 modecheck_util.m
--- compiler/modecheck_util.m	5 May 2011 03:58:55 -0000	1.5
+++ compiler/modecheck_util.m	5 May 2011 10:37:58 -0000
@@ -707,7 +707,7 @@
      ;
          PVars0 = [par_conj_mode_check(NonLocals, Bound0) | PVars1],
          ( set.member(Var0, NonLocals) ->
-            set.insert(Bound0, Var0, Bound),
+            set.insert(Var0, Bound0, Bound),
              PVars = [par_conj_mode_check(NonLocals, Bound) | PVars1]
          ;
              PVars = PVars0
Index: compiler/module_imports.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/module_imports.m,v
retrieving revision 1.10
diff -u -r1.10 module_imports.m
--- compiler/module_imports.m	7 Mar 2011 03:59:26 -0000	1.10
+++ compiler/module_imports.m	5 May 2011 13:43:33 -0000
@@ -258,7 +258,6 @@
  :- import_module dir.
  :- import_module require.
  :- import_module set.
-:- import_module svset.
  :- import_module term.

  %-----------------------------------------------------------------------------%
@@ -420,9 +419,9 @@
                  !IntImportDeps, !IntUseDeps, !ImpImportDeps, !ImpUseDeps)
          ;
              ( ModuleDefn = md_import(Modules) ->
-                svset.insert_list(Modules, !ImpImportDeps)
+                set.insert_list(Modules, !ImpImportDeps)
              ; ModuleDefn = md_use(Modules) ->
-                svset.insert_list(Modules, !ImpUseDeps)
+                set.insert_list(Modules, !ImpUseDeps)
              ;
                  true
              ),
@@ -451,9 +450,9 @@
                  !IntImportDeps, !IntUseDeps, !ImpImportDeps, !ImpUseDeps)
          ;
              ( ModuleDefn = md_import(Modules) ->
-                svset.insert_list(Modules, !IntImportDeps)
+                set.insert_list(Modules, !IntImportDeps)
              ; ModuleDefn = md_use(Modules) ->
-                svset.insert_list(Modules, !IntUseDeps)
+                set.insert_list(Modules, !IntUseDeps)
              ;
                  true
              ),
Index: compiler/module_qual.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/module_qual.m,v
retrieving revision 1.184
diff -u -r1.184 module_qual.m
--- compiler/module_qual.m	3 May 2011 04:34:56 -0000	1.184
+++ compiler/module_qual.m	5 May 2011 12:40:45 -0000
@@ -406,8 +406,8 @@
                InstanceModule = ItemInstance ^ ci_module_containing_instance,
                mq_info_get_imported_instance_modules(!.Info,
                  ImportedInstanceModules0),
-              set.insert(ImportedInstanceModules0, InstanceModule,
-                ImportedInstanceModules),
+              set.insert(InstanceModule,
+                ImportedInstanceModules0, ImportedInstanceModules),
                mq_info_set_imported_instance_modules(ImportedInstanceModules,
                  !Info)
            ;
@@ -509,7 +509,7 @@
          )
      ->
          mq_info_get_imported_modules(!.Info, Modules0),
-        set.insert_list(Modules0, Imports, Modules),
+        set.insert_list(Imports, Modules0, Modules),
          mq_info_set_imported_modules(Modules, !Info)
      ;
          true
@@ -521,7 +521,7 @@
          Status = mq_status_exported
      ->
          mq_info_get_unused_interface_modules(!.Info, UnusedIntModules0),
-        set.insert_list(UnusedIntModules0, Imports, UnusedIntModules),
+        set.insert_list(Imports, UnusedIntModules0, UnusedIntModules),
          mq_info_set_unused_interface_modules(UnusedIntModules, !Info)
      ;
          true
@@ -535,7 +535,7 @@
          )
      ->
          mq_info_get_interface_visible_modules(!.Info, IntModules0),
-        set.insert_list(IntModules0, Imports, IntModules),
+        set.insert_list(Imports, IntModules0, IntModules),
          mq_info_set_interface_visible_modules(IntModules, !Info)
      ;
          true
@@ -1935,8 +1935,8 @@
      set.list_to_set(ImportDeps `list.append` UseDeps, ImportedModules),

      % Ancestor modules are visible without being explicitly imported.
-    set.insert_list(ImportedModules,
-        [ModuleName | get_ancestors(ModuleName)], InterfaceVisibleModules),
+    set.insert_list([ModuleName | get_ancestors(ModuleName)],
+        ImportedModules, InterfaceVisibleModules),

      id_set_init(Empty),
      globals.lookup_bool_option(Globals, smart_recompilation,
@@ -2075,7 +2075,7 @@
  mq_info_set_module_used(Module, !Info) :-
      ( mq_info_get_import_status(!.Info, mq_status_exported) ->
          mq_info_get_unused_interface_modules(!.Info, Modules0),
-        set.delete(Modules0, Module, Modules),
+        set.delete(Module, Modules0, Modules),
          mq_info_set_unused_interface_modules(Modules, !Info),
          (
              Module = qualified(ParentModule, _),
@@ -2129,11 +2129,11 @@
      ),
      (
          NeedQualifier = must_be_qualified,
-        set.insert(UseModules1, Module, UseModules),
+        set.insert(Module, UseModules1, UseModules),
          ImportModules = ImportModules1
      ;
          NeedQualifier = may_be_unqualified,
-        set.insert(ImportModules1, Module, ImportModules),
+        set.insert(Module, ImportModules1, ImportModules),
          UseModules = UseModules1
      ),
      map.set(Name - Arity, ImportModules - UseModules, !IdSet).
Index: compiler/modules.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/modules.m,v
retrieving revision 1.466
diff -u -r1.466 modules.m
--- compiler/modules.m	5 May 2011 06:39:35 -0000	1.466
+++ compiler/modules.m	5 May 2011 13:43:41 -0000
@@ -393,7 +393,6 @@
  :- import_module solutions.
  :- import_module sparse_bitset.
  :- import_module string.
-:- import_module svset.
  :- import_module term.
  :- import_module unit.

@@ -1140,18 +1139,18 @@
          TypeDefn = parse_tree_eqv_type(_RhsType),
          map.search(InterfaceTypeMap, TypeCtor, _)
      ->
-        svset.insert(TypeCtor, !AbsEqvLhsTypeCtors)
+        set.insert(TypeCtor, !AbsEqvLhsTypeCtors)
      ;
          TypeDefn = parse_tree_foreign_type(_, _, _),
          map.search(InterfaceTypeMap, TypeCtor, _)
      ->
-        svset.insert(TypeCtor, !AbsEqvLhsTypeCtors)
+        set.insert(TypeCtor, !AbsEqvLhsTypeCtors)
      ;
          TypeDefn = parse_tree_du_type(Ctors, MaybeEqCmp),
          constructor_list_represents_dummy_argument_type(BothTypesMap,
              Ctors, MaybeEqCmp)
      ->
-        svset.insert(TypeCtor, !DummyTypeCtors)
+        set.insert(TypeCtor, !DummyTypeCtors)
      ;
          true
      ).
@@ -1202,7 +1201,7 @@
      % NOTE: This assumes that everything has been module qualified.
      TypeCtor = type_ctor(SymName, _Arity),
      ( sym_name_get_module_name(SymName, ModuleName) ->
-        svset.insert(ModuleName, !Modules)
+        set.insert(ModuleName, !Modules)
      ;
          unexpected($module, $pred, "unknown type encountered")
      ).
@@ -1238,7 +1237,7 @@
              % We don't need to import these modules as the types are builtin.
              true
          ;
-            svset.insert(TypeCtor, !TypeCtors)
+            set.insert(TypeCtor, !TypeCtors)
          ),
          list.foldl(type_to_type_ctor_set, Args, !TypeCtors)
      ;
@@ -1374,7 +1373,7 @@
      Constraint = constraint(ClassName, Args),
      % NOTE: This assumes that everything has been module qualified.
      ( sym_name_get_module_name(ClassName, ModuleName) ->
-        svset.insert(ModuleName, !Modules)
+        set.insert(ModuleName, !Modules)
      ;
          unexpected($module, $pred, "unknown typeclass in constraint")
      ),
@@ -1399,7 +1398,7 @@
      ;
          ArgType = defined_type(TypeName, Args, _),
          ( sym_name_get_module_name(TypeName, ModuleName) ->
-            svset.insert(ModuleName, !Modules)
+            set.insert(ModuleName, !Modules)
          ;
              unexpected($module, $pred, "unknown type encountered")
          ),
@@ -3545,7 +3544,7 @@

  accumulate_item_foreign_import_langs(Item, !LangSet) :-
      Langs = item_needs_foreign_imports(Item),
-    svset.insert_list(Langs, !LangSet).
+    set.insert_list(Langs, !LangSet).

  :- pred get_interface_and_implementation_2(bool::in, list(item)::in, bool::in,
      list(item)::in, list(item)::out,
Index: compiler/opt_util.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/opt_util.m,v
retrieving revision 1.174
diff -u -r1.174 opt_util.m
--- compiler/opt_util.m	25 Mar 2011 03:13:40 -0000	1.174
+++ compiler/opt_util.m	5 May 2011 11:35:52 -0000
@@ -2173,7 +2173,7 @@
      ;
          Instr = Instr0,
          ( Uinstr0 = assign(Lval, _) ->
-            set.delete(Livevals0, Lval, Livevals)
+            set.delete(Lval, Livevals0, Livevals)
          ; can_instr_fall_through(Uinstr0) = no ->
              set.init(Livevals)
          ;
Index: compiler/ordering_mode_constraints.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/ordering_mode_constraints.m,v
retrieving revision 1.31
diff -u -r1.31 ordering_mode_constraints.m
--- compiler/ordering_mode_constraints.m	3 May 2011 04:34:57 -0000	1.31
+++ compiler/ordering_mode_constraints.m	5 May 2011 13:43:48 -0000
@@ -124,7 +124,6 @@
  :- import_module multi_map.
  :- import_module require.
  :- import_module string.
-:- import_module svset.

  %-----------------------------------------------------------------------------%
  %
@@ -468,7 +467,7 @@
      is det.

  insert_lt_constraint(A, B, !Cs) :-
-    svset.insert(lt(A, B), !Cs).
+    set.insert(lt(A, B), !Cs).

  %-----------------------------------------------------------------------------%

@@ -666,11 +665,11 @@

  topological_sort_min_reordering(Constraints0, Conjuncts0, Ordering) :-
      NotFirst = set.map(func(lt(_From, To)) = To, Constraints0),
-    CantidatesForFirst = set.difference(Conjuncts0, NotFirst),
+    CandidatesForFirst = set.difference(Conjuncts0, NotFirst),

-    ( set.remove_least(CantidatesForFirst, First, _) ->
+    ( set.remove_least(First, CandidatesForFirst, _) ->
          % Remove First from the system.
-        set.remove(Conjuncts0, First, Conjuncts),
+        set.remove(First, Conjuncts0, Conjuncts),
          Constraints = set.filter(
              (pred(lt(From, _To)::in) is semidet :- From \= First),
              Constraints0),
Index: compiler/pd_info.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/pd_info.m,v
retrieving revision 1.44
diff -u -r1.44 pd_info.m
--- compiler/pd_info.m	3 May 2011 04:34:57 -0000	1.44
+++ compiler/pd_info.m	5 May 2011 13:10:46 -0000
@@ -687,7 +687,7 @@
      map.det_insert(PredProcId, Version, Versions0, Versions),
      pd_info_set_versions(Versions, !PDInfo),
      pd_info_get_created_versions(!.PDInfo, CreatedVersions0),
-    set.insert(CreatedVersions0, PredProcId, CreatedVersions),
+    set.insert(PredProcId, CreatedVersions0, CreatedVersions),
      pd_info_set_created_versions(CreatedVersions, !PDInfo).

  %-----------------------------------------------------------------------------%
@@ -704,7 +704,7 @@
          % Make sure we never create another version to deforest
          % this pair of calls.
          pd_info_get_useless_versions(!.PDInfo, Useless0),
-        set.insert(Useless0, FirstCall - LastCall, Useless),
+        set.insert(FirstCall - LastCall, Useless0, Useless),
          pd_info_set_useless_versions(Useless, !PDInfo)
      ;
          true
@@ -729,7 +729,7 @@
      ),

      pd_info_get_created_versions(!.PDInfo, CreatedVersions0),
-    set.delete(CreatedVersions0, PredProcId, CreatedVersions),
+    set.delete(PredProcId, CreatedVersions0, CreatedVersions),
      pd_info_set_created_versions(CreatedVersions, !PDInfo),

      pd_info_get_module_info(!.PDInfo, ModuleInfo0),
Index: compiler/pd_util.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/pd_util.m,v
retrieving revision 1.80
diff -u -r1.80 pd_util.m
--- compiler/pd_util.m	3 May 2011 04:34:57 -0000	1.80
+++ compiler/pd_util.m	5 May 2011 13:15:01 -0000
@@ -177,7 +177,6 @@
  :- import_module require.
  :- import_module set.
  :- import_module term.
-:- import_module svset.

  goal_get_calls(Goal0, CalledPreds) :-
      goal_to_conj_list(Goal0, GoalList),
@@ -352,7 +351,7 @@
      ( inst_is_clobbered(ModuleInfo, FinalInst) ->
          true
      ;
-        svset.insert(NonLocal, !Vars)
+        set.insert(NonLocal, !Vars)
      ),
      get_goal_live_vars_2(ModuleInfo, NonLocals, InstMap, InstMapDelta, !Vars).

@@ -479,7 +478,7 @@
          mode_is_output(ModuleInfo, ArgMode),
          \+ map.contains(ExtraInfoArgs, ArgNo)
      ->
-        set.insert(!.OpaqueArgs, ArgNo, !:OpaqueArgs)
+        set.insert(ArgNo, !OpaqueArgs)
      ;
          true
      ),
@@ -505,7 +504,7 @@
          true
      ),
      ( set.member(HeadVar, LeftVars) ->
-        svset.insert(ArgNo, !ThisProcLeftVars)
+        set.insert(ArgNo, !ThisProcLeftVars)
      ;
          true
      ),
@@ -607,7 +606,7 @@

  get_left_vars(Goal, Vars0, Vars) :-
      ( Goal = hlds_goal(switch(Var, _, _), _) ->
-        set.insert(Vars0, Var, Vars)
+        set.insert(Var, Vars0, Vars)
      ;
          Vars = Vars0
      ).
@@ -629,7 +628,7 @@
                  \+ inst_is_bound_to_functors(ModuleInfo, VarInst, [_])
              ->
                  ( map.search(Vars0, ChangedVar, Set0) ->
-                    set.insert(Set0, BranchNo, Set)
+                    set.insert(BranchNo, Set0, Set)
                  ;
                      set.singleton_set(Set, BranchNo)
                  ),
@@ -646,7 +645,7 @@
      % at the end of each branch.
      ( Goal = hlds_goal(switch(SwitchVar, _, _), _) ->
          ( map.search(!.ExtraVars, SwitchVar, SwitchVarSet0) ->
-            set.insert(SwitchVarSet0, BranchNo, SwitchVarSet)
+            set.insert(BranchNo, SwitchVarSet0, SwitchVarSet)
          ;
              set.singleton_set(SwitchVarSet, BranchNo)
          ),
@@ -780,7 +779,7 @@
  combine_vars(_, [], !Vars).
  combine_vars(BranchNo, [ExtraVar | ExtraVars], !Vars) :-
      ( map.search(!.Vars, ExtraVar, Branches0) ->
-        set.insert(Branches0, BranchNo, Branches),
+        set.insert(BranchNo, Branches0, Branches),
          map.det_update(ExtraVar, Branches, !Vars)
      ;
          set.singleton_set(Branches, BranchNo),
@@ -826,20 +825,20 @@
  :- pred inst_MSG_1(mer_inst::in, mer_inst::in, expansions::in, module_info::in,
      mer_inst::out) is semidet.

-inst_MSG_1(InstA, InstB, Expansions, ModuleInfo, Inst) :-
+inst_MSG_1(InstA, InstB, !.Expansions, ModuleInfo, Inst) :-
      ( InstA = InstB ->
          Inst = InstA
      ;
          % We don't do recursive MSGs
          % (we could, but it's probably not worth it).
-        \+ set.member(InstA - InstB, Expansions),
+        \+ set.member(InstA - InstB, !.Expansions),
          inst_expand(ModuleInfo, InstA, InstA2),
          inst_expand(ModuleInfo, InstB, InstB2),
-        set.insert(Expansions, InstA - InstB, Expansions1),
+        set.insert(InstA - InstB, !Expansions),
          ( InstB2 = not_reached ->
              Inst = InstA2
          ;
-            inst_MSG_2(InstA2, InstB2, Expansions1, ModuleInfo, Inst)
+            inst_MSG_2(InstA2, InstB2, !.Expansions, ModuleInfo, Inst)
          )
      ).

@@ -942,13 +941,13 @@
          Size) :-
      inst_size_2(ModuleInfo, Inst, Expansions, Size).
  inst_size_2(_, abstract_inst(_, _), _, 0).
-inst_size_2(ModuleInfo, defined_inst(InstName), Expansions0, Size) :-
-    ( set.member(InstName, Expansions0) ->
+inst_size_2(ModuleInfo, defined_inst(InstName), !.Expansions, Size) :-
+    ( set.member(InstName, !.Expansions) ->
          Size = 1
      ;
-        set.insert(Expansions0, InstName, Expansions),
+        set.insert(InstName, !Expansions),
          inst_lookup(ModuleInfo, InstName, Inst),
-        inst_size_2(ModuleInfo, Inst, Expansions, Size)
+        inst_size_2(ModuleInfo, Inst, !.Expansions, Size)
      ).
  inst_size_2(ModuleInfo, bound(_, Functors), Expansions, Size) :-
      bound_inst_size(ModuleInfo, Functors, Expansions, 1, Size).
@@ -996,7 +995,7 @@
      list.map(Search, OldArgs, NewArgs),
      NewGoal = hlds_goal(_, NewGoalInfo),
      NewNonLocals = goal_info_get_nonlocals(NewGoalInfo),
-    set.delete_list(NewNonLocals, NewArgs, UnmatchedNonLocals),
+    set.delete_list(NewArgs, NewNonLocals, UnmatchedNonLocals),
      set.empty(UnmatchedNonLocals),

      % Check that argument types of NewGoal are subsumed by those of OldGoal.
Index: compiler/polymorphism.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/polymorphism.m,v
retrieving revision 1.361
diff -u -r1.361 polymorphism.m
--- compiler/polymorphism.m	5 May 2011 07:11:50 -0000	1.361
+++ compiler/polymorphism.m	5 May 2011 10:45:25 -0000
@@ -1434,7 +1434,7 @@
      % Insert the TypeInfoVars into the nonlocals field of the goal_info
      % for the unification goal.
      NonLocals0 = goal_info_get_nonlocals(!.GoalInfo),
-    set.insert_list(NonLocals0, TypeInfoVars, NonLocals),
+    set.insert_list(TypeInfoVars, NonLocals0, NonLocals),
      goal_info_set_nonlocals(NonLocals, !GoalInfo),

      % Also save those type_info vars into a field in the complicated_unify,
@@ -1555,7 +1555,7 @@
              ExtraVars, ExtraGoals, !Info),
          ArgVars = ExtraVars ++ ArgVars0,
          NonLocals0 = goal_info_get_nonlocals(GoalInfo0),
-        set.insert_list(NonLocals0, ExtraVars, NonLocals),
+        set.insert_list(ExtraVars, NonLocals0, NonLocals),
          goal_info_set_nonlocals(NonLocals, GoalInfo0, GoalInfo1),

          % Some of the argument unifications may be complicated unifications,
@@ -1608,7 +1608,7 @@
      % to compute constraint_ids correctly.

      NonLocals = goal_info_get_nonlocals(GoalInfo0),
-    set.insert_list(NonLocals, LambdaVars, OutsideVars),
+    set.insert_list(LambdaVars, NonLocals, OutsideVars),
      set.list_to_set(Args, InsideVars),
      set.intersect(OutsideVars, InsideVars, LambdaNonLocals),
      GoalId = goal_info_get_goal_id(GoalInfo0),
@@ -2130,7 +2130,7 @@

          % Update the nonlocals.
          NonLocals0 = goal_info_get_nonlocals(GoalInfo0),
-        set.insert_list(NonLocals0, ExtraVars, NonLocals),
+        set.insert_list(ExtraVars, NonLocals0, NonLocals),
          goal_info_set_nonlocals(NonLocals, GoalInfo0, GoalInfo)
      ).

@@ -2276,8 +2276,8 @@
          poly_info_get_var_types(!.Info, VarTypes0),
          !.Goal = hlds_goal(_, GoalInfo0),
          NonLocals = goal_info_get_nonlocals(GoalInfo0),
-        set.insert_list(NonLocals, ArgVars, NonLocalsPlusArgs0),
-        set.insert_list(NonLocalsPlusArgs0, LambdaVars, NonLocalsPlusArgs),
+        set.insert_list(ArgVars, NonLocals, NonLocalsPlusArgs0),
+        set.insert_list(LambdaVars, NonLocalsPlusArgs0, NonLocalsPlusArgs),
          goal_util.extra_nonlocal_typeinfos(RttiVarMaps0, VarTypes0,
              ExistQVars, NonLocalsPlusArgs, NewOutsideVars),
          set.union(NonLocals, NewOutsideVars, OutsideVars),
Index: compiler/post_typecheck.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/post_typecheck.m,v
retrieving revision 1.147
diff -u -r1.147 post_typecheck.m
--- compiler/post_typecheck.m	5 May 2011 03:58:55 -0000	1.147
+++ compiler/post_typecheck.m	5 May 2011 10:47:29 -0000
@@ -320,7 +320,7 @@
      ;
          type_vars(Type, TVars),
          set.list_to_set(TVars, TVarsSet0),
-        set.delete_list(TVarsSet0, HeadTypeParams, TVarsSet1),
+        set.delete_list(HeadTypeParams, TVarsSet0, TVarsSet1),
          ( set.empty(TVarsSet1) ->
              true
          ;
@@ -1354,7 +1354,7 @@
      DeconstructArgs = VarsBeforeField ++ [SingletonFieldVar | VarsAfterField],
      OldNonLocals = goal_info_get_nonlocals(OldGoalInfo),
      NonLocalArgs = VarsBeforeField ++ VarsAfterField,
-    set.insert_list(OldNonLocals, NonLocalArgs, DeconstructRestrictNonLocals),
+    set.insert_list(NonLocalArgs, OldNonLocals, DeconstructRestrictNonLocals),

      create_pure_atomic_unification_with_nonlocals(TermInputVar,
          rhs_functor(ConsId0, no, DeconstructArgs), OldGoalInfo,
@@ -1363,7 +1363,7 @@

      % Build a goal to construct the output.
      ConstructArgs = VarsBeforeField ++ [FieldVar | VarsAfterField],
-    set.insert_list(OldNonLocals, NonLocalArgs, ConstructRestrictNonLocals),
+    set.insert_list(NonLocalArgs, OldNonLocals, ConstructRestrictNonLocals),

      % If the cons_id is existentially quantified, add a `new' prefix
      % so that polymorphism.m adds the appropriate type_infos.
Index: compiler/pragma_c_gen.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/pragma_c_gen.m,v
retrieving revision 1.119
diff -u -r1.119 pragma_c_gen.m
--- compiler/pragma_c_gen.m	30 Dec 2010 11:17:57 -0000	1.119
+++ compiler/pragma_c_gen.m	5 May 2011 11:36:51 -0000
@@ -395,7 +395,7 @@
      (
          Expr = trace_base(trace_envvar(EnvVar)),
          get_used_env_vars(!.CI, UsedEnvVars0),
-        set.insert(UsedEnvVars0, EnvVar, UsedEnvVars),
+        set.insert(EnvVar, UsedEnvVars0, UsedEnvVars),
          set_used_env_vars(UsedEnvVars, !CI),
          EnvVarRval = lval(global_var_ref(env_var_ref(EnvVar))),
          ZeroRval = const(llconst_int(0)),
@@ -896,7 +896,7 @@
  find_dead_input_vars([Arg | Args], PostDeaths, !DeadVars) :-
      Arg = c_arg(Var, _MaybeName, _Type, _BoxPolicy, _ArgInfo),
      ( set.member(Var, PostDeaths) ->
-        set.insert(!.DeadVars, Var, !:DeadVars)
+        set.insert(Var, !DeadVars)
      ;
          true
      ),
Index: compiler/proc_gen.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/proc_gen.m,v
retrieving revision 1.44
diff -u -r1.44 proc_gen.m
--- compiler/proc_gen.m	25 Mar 2011 03:13:40 -0000	1.44
+++ compiler/proc_gen.m	5 May 2011 11:38:45 -0000
@@ -1117,7 +1117,7 @@
                  )
              ),
              solutions.solutions(FindBaseLvals, TypeInfoLvals),
-            set.insert_list(OutLvals, TypeInfoLvals, LiveLvals)
+            set.insert_list(TypeInfoLvals, OutLvals, LiveLvals)
          ;
              MaybeTraceInfo = no,
              TraceExitCode = empty,
@@ -1140,7 +1140,7 @@
              CodeModel = model_semi,
              expect(unify(MaybeSpecialReturn, no), this_file,
                  "generate_exit: semi special_return"),
-            set.insert(LiveLvals, reg(reg_r, 1), SuccessLiveRegs),
+            set.insert(reg(reg_r, 1), LiveLvals, SuccessLiveRegs),
              SuccessCode = from_list([
                  llds_instr(assign(reg(reg_r, 1), const(llconst_true)),
                      "Succeed"),
@@ -1204,7 +1204,7 @@
          % XXX We should also test for tailcalls
          % once we start generating them directly.
      ->
-        set.insert(LiveVals0, stackvar(StackLoc), LiveVals1),
+        set.insert(stackvar(StackLoc), LiveVals0, LiveVals1),
          Uinstr = livevals(LiveVals1),
          Instr = llds_instr(Uinstr, Comment)
      ;
Index: compiler/prog_event.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/prog_event.m,v
retrieving revision 1.20
diff -u -r1.20 prog_event.m
--- compiler/prog_event.m	3 May 2011 04:34:57 -0000	1.20
+++ compiler/prog_event.m	5 May 2011 12:41:57 -0000
@@ -74,7 +74,6 @@
  :- import_module require.
  :- import_module set.
  :- import_module string.
-:- import_module svset.
  :- import_module term.

  read_event_set(SpecsFileName, EventSetName, EventSpecMap, ErrorSpecs, !IO) :-
@@ -711,11 +710,11 @@
                  AttrTerm = event_attr_type_synthesized(_, SynthCall),
                  SynthCall = event_attr_synth_call_term(FuncAttrName,
                      ArgAttrNames),
-                set.insert(Ancestors, AttrName, SubAncestors),
+                set.insert(AttrName, Ancestors, SubAncestors),
                  compute_prev_synth_attr_order_for_args(AttrNameMap,
                      [FuncAttrName | ArgAttrNames], SubAncestors,
                      !AlreadyComputed, SubPrevSynthOrder),
-                svset.insert(AttrName, !AlreadyComputed),
+                set.insert(AttrName, !AlreadyComputed),
                  % This append at the end makes our algorithm O(n^2),
                  % but since n will always be small, this doesn't matter.
                  AttrNum = AttrInfo ^ attr_info_number,
Index: compiler/prop_mode_constraints.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/prop_mode_constraints.m,v
retrieving revision 1.32
diff -u -r1.32 prop_mode_constraints.m
--- compiler/prop_mode_constraints.m	5 May 2011 03:58:56 -0000	1.32
+++ compiler/prop_mode_constraints.m	5 May 2011 13:43:53 -0000
@@ -93,7 +93,6 @@
  :- import_module require.
  :- import_module set.
  :- import_module string.
-:- import_module svset.
  :- import_module term.
  :- import_module varset.

@@ -454,7 +453,7 @@
      ;
          Var = Var0
      ),
-    svset.insert(Var, !SeenSoFar).
+    set.insert(Var, !SeenSoFar).

      % replace_call_with_conjunction(NewCallGoalExpr, Unifications, NewArgs,
      %   GoalExpr, !GoalInfo):
Index: compiler/purity.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/purity.m,v
retrieving revision 1.143
diff -u -r1.143 purity.m
--- compiler/purity.m	3 May 2011 04:34:57 -0000	1.143
+++ compiler/purity.m	5 May 2011 10:47:56 -0000
@@ -809,7 +809,7 @@
      % OuterDI and OuterUO will definitely be used by the code inside the new
      % goal, and *should* be used by code outside the goal. However, even if
      % they are not, the nonlocals set is allowed to overapproximate.
-    set.insert_list(NonLocals0, [OuterDI, OuterUO], NonLocals),
+    set.insert_list([OuterDI, OuterUO], NonLocals0, NonLocals),
      goal_info_set_nonlocals(NonLocals, GoalInfo0, GoalInfo1),
      goal_info_add_feature(feature_contains_stm_inner_outer, GoalInfo1,
          GoalInfo),
Index: compiler/rbmm.condition_renaming.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/rbmm.condition_renaming.m,v
retrieving revision 1.17
diff -u -r1.17 rbmm.condition_renaming.m
--- compiler/rbmm.condition_renaming.m	3 May 2011 04:34:57 -0000	1.17
+++ compiler/rbmm.condition_renaming.m	5 May 2011 13:44:02 -0000
@@ -147,7 +147,6 @@
  :- import_module require.
  :- import_module set.
  :- import_module string.
-:- import_module svset.

  %-----------------------------------------------------------------------------%

@@ -400,9 +399,9 @@
      RegionName = rptg_lookup_region_name(Graph, Node),
      ( map.search(Renaming, RegionName, RenamedRegionNameList) ->
          RenamedRegionName = list.det_last(RenamedRegionNameList),
-        svset.insert(RenamedRegionName, !Regions)
+        set.insert(RenamedRegionName, !Regions)
      ;
-        svset.insert(RegionName, !Regions)
+        set.insert(RegionName, !Regions)
      ).

  :- pred renaming_annotation_to_regions(region_instr::in,
@@ -418,8 +417,8 @@
          unexpected($module, $pred, "annotation is not assignment")
      ;
          RenameAnnotation = rename_region(RightRegion, LeftRegion),
-        svset.insert(LeftRegion, !LeftRegions),
-        svset.insert(RightRegion, !RightRegions)
+        set.insert(LeftRegion, !LeftRegions),
+        set.insert(RightRegion, !RightRegions)
      ).

      % The non-local regions of an if-then-else will be attached to
Index: compiler/rbmm.interproc_region_lifetime.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/rbmm.interproc_region_lifetime.m,v
retrieving revision 1.9
diff -u -r1.9 rbmm.interproc_region_lifetime.m
--- compiler/rbmm.interproc_region_lifetime.m	3 May 2011 04:34:57 -0000	1.9
+++ compiler/rbmm.interproc_region_lifetime.m	5 May 2011 13:44:11 -0000
@@ -75,7 +75,6 @@
  :- import_module require.
  :- import_module set.
  :- import_module solutions.
-:- import_module svset.

  %-----------------------------------------------------------------------------%
  %
@@ -428,9 +427,9 @@
      ( if
          set.contains(!.Candidates, Target)
        then
-        svset.insert(Target, !Targets)
+        set.insert(Target, !Targets)
        else
-        svset.insert(Target, !Candidates)
+        set.insert(Target, !Candidates)
      ).

      % This predicate propagates the removal of a region from a deadR or
@@ -528,11 +527,12 @@

  :- pred find_alpha_source(rptg_node::in, rptg_node::in, rptg_node::in,
      set(rptg_node)::in, set(rptg_node)::out) is det.
+
  find_alpha_source(ToBeRemovedRegion, Source, Target, !Rs) :-
      ( if
          ToBeRemovedRegion = Target
        then
-        set.insert(!.Rs, Source, !:Rs)
+        set.insert(Source, !Rs)
        else
          true
      ).
@@ -583,7 +583,7 @@
      ( type_not_stored_in_region(NodeType, ModuleInfo) ->
          true
      ;
-        svset.insert(Region, !RegionSet)
+        set.insert(Region, !RegionSet)
      ).

      % Eliminate regions of primitive types from the proc_pp_region_set_table.
Index: compiler/rbmm.live_variable_analysis.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/rbmm.live_variable_analysis.m,v
retrieving revision 1.8
diff -u -r1.8 rbmm.live_variable_analysis.m
--- compiler/rbmm.live_variable_analysis.m	3 May 2011 04:34:57 -0000	1.8
+++ compiler/rbmm.live_variable_analysis.m	5 May 2011 13:16:01 -0000
@@ -393,7 +393,7 @@
      mercury_var_to_string(Varset, no, Var) = VarName,
      string.substring(VarName, 0, 1, FirstChar),
      ( FirstChar = "_" ->
-        set.insert(!.VoidVars, Var, !:VoidVars)
+        set.insert(Var, !VoidVars)
      ;
          true
      ).
Index: compiler/rbmm.points_to_graph.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/rbmm.points_to_graph.m,v
retrieving revision 1.8
diff -u -r1.8 rbmm.points_to_graph.m
--- compiler/rbmm.points_to_graph.m	3 May 2011 04:34:58 -0000	1.8
+++ compiler/rbmm.points_to_graph.m	5 May 2011 13:44:33 -0000
@@ -274,7 +274,6 @@
  :- import_module pair.
  :- import_module require.
  :- import_module solutions.
-:- import_module svset.
  :- import_module term.

      % A region points-to graph (rpt_graph) is a directed graph in which
@@ -981,7 +980,7 @@
      Node_Selector = Node - Selector,

      % Add the "remembered" Node to reach_from_x set
-    svset.insert(Node, !Reach_X),
+    set.insert(Node, !Reach_X),

      % Add the Node to processed list so that we do not have to deal with
      % it more than once. (Node is not yet in Processed0 because if it
Index: compiler/rbmm.points_to_info.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/rbmm.points_to_info.m,v
retrieving revision 1.6
diff -u -r1.6 rbmm.points_to_info.m
--- compiler/rbmm.points_to_info.m	30 Dec 2010 11:17:57 -0000	1.6
+++ compiler/rbmm.points_to_info.m	5 May 2011 13:16:32 -0000
@@ -100,7 +100,7 @@
  add_node_from_var(VarTypes, Var, Reg0, Reg, !Graph) :-
      map.lookup(VarTypes, Var, NodeType),
      set.init(Varset0),
-    set.insert(Varset0, Var, Varset),
+    set.insert(Var, Varset0, Varset),
      Reg = Reg0 + 1,
      string.append("R", string.int_to_string(Reg0), RegName),
      NodeInfo = rptg_node_content(Varset, RegName, set.init, NodeType, bool.no),
Index: compiler/rbmm.region_instruction.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/rbmm.region_instruction.m,v
retrieving revision 1.13
diff -u -r1.13 rbmm.region_instruction.m
--- compiler/rbmm.region_instruction.m	3 May 2011 04:34:58 -0000	1.13
+++ compiler/rbmm.region_instruction.m	5 May 2011 13:44:45 -0000
@@ -114,7 +114,6 @@
  :- import_module require.
  :- import_module set.
  :- import_module string.
-:- import_module svset.

  introduce_region_instructions(ModuleInfo, RptaInfoTable, ExecPathTable,
          LRBeforeTable, LRAfterTable, VoidVarRegionTable, BornRTable,
@@ -420,7 +419,7 @@
          set.contains(BecomeLive, TargetRegion),
          not set.contains(CalleeBornR, SourceRegion)
      ->
-        svset.insert(TargetRegion, !CreatedBeforeProgPoint)
+        set.insert(TargetRegion, !CreatedBeforeProgPoint)
      ;
          true
      ).
@@ -438,7 +437,7 @@
          set.contains(BecomeDead, TargetRegion),
          not set.contains(CalleeDeadR, SourceRegion)
      ->
-        svset.insert(TargetRegion, !RemovedAfterProgPoint)
+        set.insert(TargetRegion, !RemovedAfterProgPoint)
      ;
          true
      ).
Index: compiler/rbmm.region_resurrection_renaming.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/rbmm.region_resurrection_renaming.m,v
retrieving revision 1.11
diff -u -r1.11 rbmm.region_resurrection_renaming.m
--- compiler/rbmm.region_resurrection_renaming.m	5 May 2011 06:39:36 -0000	1.11
+++ compiler/rbmm.region_resurrection_renaming.m	5 May 2011 13:44:54 -0000
@@ -159,7 +159,6 @@
  :- import_module require.
  :- import_module set.
  :- import_module string.
-:- import_module svset.

  %-----------------------------------------------------------------------------%

@@ -326,7 +325,7 @@
                      map.set(PrevPoint, JPName, !JP2Name)
                  ),
                  map.set(ProgPoint, JPName, !JoinPointProc),
-                svset.insert(ProgPoint, !JoinPoints)
+                set.insert(ProgPoint, !JoinPoints)
              ;
                  true
              )
@@ -422,7 +421,7 @@

  find_join_points_in_path(ProgPointsInPath, JoinPoint, _, !JoinPoints) :-
      ( list.member(JoinPoint, ProgPointsInPath) ->
-        svset.insert(JoinPoint, !JoinPoints)
+        set.insert(JoinPoint, !JoinPoints)
      ;
          true
      ).
Index: compiler/reassign.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/reassign.m,v
retrieving revision 1.34
diff -u -r1.34 reassign.m
--- compiler/reassign.m	3 May 2011 04:34:58 -0000	1.34
+++ compiler/reassign.m	5 May 2011 11:40:13 -0000
@@ -449,7 +449,7 @@

  make_not_dependent(Target, SubLval, !DepLvalMap) :-
      ( map.search(!.DepLvalMap, SubLval, DepLvals0) ->
-        set.delete(DepLvals0, Target, DepLvals),
+        set.delete(Target, DepLvals0, DepLvals),
          map.det_update(SubLval, DepLvals, !DepLvalMap)
      ;
          true
@@ -460,7 +460,7 @@

  make_dependent(Target, SubLval, !DepLvalMap) :-
      ( map.search(!.DepLvalMap, SubLval, DepLvals0) ->
-        set.insert(DepLvals0, Target, DepLvals),
+        set.insert(Target, DepLvals0, DepLvals),
          map.det_update(SubLval, DepLvals, !DepLvalMap)
      ;
          DepLvals = set.make_singleton_set(Target),
Index: compiler/recompilation.usage.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/recompilation.usage.m,v
retrieving revision 1.56
diff -u -r1.56 recompilation.usage.m
--- compiler/recompilation.usage.m	5 May 2011 07:11:51 -0000	1.56
+++ compiler/recompilation.usage.m	5 May 2011 12:51:08 -0000
@@ -1026,7 +1026,7 @@
          ;
              set.init(ClassIds1)
          ),
-        set.insert(ClassIds1, ClassId, ClassIds),
+        set.insert(ClassId, ClassIds1, ClassIds),
          map.set(InstanceModuleName, ClassIds,
              ModuleInstances0, ModuleInstances),
          !Info ^ module_instances := ModuleInstances
@@ -1421,7 +1421,7 @@
  maybe_record_item_to_process(ItemType, ItemName, !Info) :-
      ( ItemType = typeclass_item ->
          Classes0 = !.Info ^ used_typeclasses,
-        set.insert(Classes0, ItemName, Classes),
+        set.insert(ItemName, Classes0, Classes),
          !Info ^ used_typeclasses := Classes
      ;
          true
@@ -1478,7 +1478,7 @@
          ModuleItems1 = init_item_id_set(set.init)
      ),
      ModuleItemIds0 = extract_ids(ModuleItems1, ItemType),
-    set.insert(ModuleItemIds0, Name - Arity, ModuleItemIds),
+    set.insert(Name - Arity, ModuleItemIds0, ModuleItemIds),
      ModuleItems = update_ids(ModuleItems1, ItemType, ModuleItemIds),
      map.set(Module, ModuleItems, ImportedItems0, ImportedItems),
      !Info ^ imported_items := ImportedItems.
Index: compiler/simplify.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/simplify.m,v
retrieving revision 1.261
diff -u -r1.261 simplify.m
--- compiler/simplify.m	5 May 2011 06:39:36 -0000	1.261
+++ compiler/simplify.m	5 May 2011 10:53:00 -0000
@@ -1214,7 +1214,7 @@
                  % Work out the nonlocals, instmap_delta
                  % and determinism of the entire conjunction.
                  NonLocals0 = goal_info_get_nonlocals(GoalInfo0),
-                set.insert(NonLocals0, Var, NonLocals),
+                set.insert(Var, NonLocals0, NonLocals),
                  InstMapDelta0 = goal_info_get_instmap_delta(GoalInfo0),
                  simplify_info_get_instmap(!.Info, InstMap),
                  instmap_delta_bind_var_to_functor(Var, Type, MainConsId,
@@ -2713,7 +2713,7 @@

      OpGoalInfo0 = !.GoalInfo,
      OpNonLocals0 = goal_info_get_nonlocals(OpGoalInfo0),
-    set.insert(OpNonLocals0, ConstVar, OpNonLocals),
+    set.insert(ConstVar, OpNonLocals0, OpNonLocals),
      goal_info_set_nonlocals(OpNonLocals, OpGoalInfo0, OpGoalInfo),
      OpGoal = hlds_goal(OpGoalExpr, OpGoalInfo),

@@ -2966,7 +2966,7 @@

      % Add the extra type_info vars to the nonlocals for the call.
      NonLocals0 = goal_info_get_nonlocals(GoalInfo0),
-    set.insert_list(NonLocals0, TypeInfoVars, NonLocals),
+    set.insert_list(TypeInfoVars, NonLocals0, NonLocals),
      goal_info_set_nonlocals(NonLocals, GoalInfo0, CallGoalInfo).

  :- pred call_builtin_compound_eq(prog_var::in, prog_var::in, module_info::in,
Index: compiler/size_prof.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/size_prof.m,v
retrieving revision 1.69
diff -u -r1.69 size_prof.m
--- compiler/size_prof.m	5 May 2011 03:58:56 -0000	1.69
+++ compiler/size_prof.m	5 May 2011 13:17:00 -0000
@@ -750,7 +750,7 @@
              construct_sub_info(no, yes(dynamic_size(SizeVar)))),
          UnifyExpr = unify(LHS, RHS, UniMode, Unification, UnifyContext),
          NonLocals0 = goal_info_get_nonlocals(GoalInfo0),
-        set.insert(NonLocals0, SizeVar, NonLocals),
+        set.insert(SizeVar, NonLocals0, NonLocals),
          goal_info_set_nonlocals(NonLocals, GoalInfo0, GoalInfo),
          UnifyGoal = hlds_goal(UnifyExpr, GoalInfo),
          Goals = list.condense([ArgGoals, SizeGoals, [UnifyGoal]]),
Index: compiler/stack_alloc.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/stack_alloc.m,v
retrieving revision 1.27
diff -u -r1.27 stack_alloc.m
--- compiler/stack_alloc.m	3 May 2011 04:34:58 -0000	1.27
+++ compiler/stack_alloc.m	5 May 2011 11:41:14 -0000
@@ -93,7 +93,7 @@
      (
          MaybeReservedVarInfo = yes(ResVar - _),
          set.singleton_set(ResVarSet, ResVar),
-        set.insert(LiveSets0, ResVarSet, LiveSets1)
+        set.insert(ResVarSet, LiveSets0, LiveSets1)
      ;
          MaybeReservedVarInfo = no,
          LiveSets1 = LiveSets0
@@ -133,7 +133,7 @@
      set.to_sorted_list(LiveSet0, LiveList0),
      list.filter(var_is_of_dummy_type(ModuleInfo, VarTypes), LiveList0,
          DummyVars, NonDummyVars),
-    set.insert_list(!.Dummies, DummyVars, !:Dummies),
+    set.insert_list(DummyVars, !Dummies),
      (
          NonDummyVars = [],
          LiveSets = LiveSets1
Index: compiler/stack_layout.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/stack_layout.m,v
retrieving revision 1.157
diff -u -r1.157 stack_layout.m
--- compiler/stack_layout.m	5 May 2011 06:39:36 -0000	1.157
+++ compiler/stack_layout.m	5 May 2011 11:41:40 -0000
@@ -1700,7 +1700,7 @@
      term.var_to_int(TVar, TVarNum),
      NextSlot = CurSlot + 1,
      ( TVarNum = CurSlot ->
-        ( set.remove_least(Locns, LeastLocn, _) ->
+        ( set.remove_least(LeastLocn, Locns, _) ->
              Locn = LeastLocn
          ;
              unexpected(this_file, "tvar has empty set of locations")
Index: compiler/stack_opt.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/stack_opt.m,v
retrieving revision 1.51
diff -u -r1.51 stack_opt.m
--- compiler/stack_opt.m	5 May 2011 07:11:51 -0000	1.51
+++ compiler/stack_opt.m	5 May 2011 13:45:08 -0000
@@ -116,7 +116,6 @@
  :- import_module pair.
  :- import_module require.
  :- import_module set.
-:- import_module svset.
  :- import_module term.

  %-----------------------------------------------------------------------------%
@@ -579,7 +578,7 @@
      record_interval_vars(IntervalId, [CellVar], !IntervalInfo),
      delete_interval_vars(IntervalId, ViaCellVars, DeletedVars, !IntervalInfo),
      ( set.non_empty(DeletedVars) ->
-        svset.insert(IntervalId, !InsertIntervals)
+        set.insert(IntervalId, !InsertIntervals)
      ;
          true
      ).
@@ -606,7 +605,7 @@
              map.det_insert(Anchor, Inserts, InsertMap0, InsertMap)
          ),
          !StackOptInfo ^ soi_left_anchor_inserts := InsertMap,
-        svset.insert(Anchor, !InsertAnchors)
+        set.insert(Anchor, !InsertAnchors)
      ;
          true
      ).
@@ -685,7 +684,7 @@
          CurSegment0 = !.Path ^ current_segment,
          CurSegment = set.union(Vars, CurSegment0),
          OccurringIntervals0 = !.Path ^ occurring_intervals,
-        svset.insert(IntervalId, OccurringIntervals0, OccurringIntervals),
+        set.insert(IntervalId, OccurringIntervals0, OccurringIntervals),
          !Path ^ current_segment := CurSegment,
          !Path ^ occurring_intervals := OccurringIntervals
      ).
@@ -694,7 +693,7 @@

  add_anchor_to_path(Anchor, !.Path) = !:Path :-
      Anchors0 = !.Path ^ flush_anchors,
-    svset.insert(Anchor, Anchors0, Anchors),
+    set.insert(Anchor, Anchors0, Anchors),
      !Path ^ flush_anchors := Anchors.

  :- func anchor_requires_close(interval_info, anchor) = bool.
Index: compiler/stm_expand.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/stm_expand.m,v
retrieving revision 1.19
diff -u -r1.19 stm_expand.m
--- compiler/stm_expand.m	5 May 2011 07:11:51 -0000	1.19
+++ compiler/stm_expand.m	5 May 2011 13:22:19 -0000
@@ -622,12 +622,12 @@
      goal_vars(HldsGoal, GoalVars0),
      HldsGoal = hlds_goal(_, GoalInfo),

-    set.delete_list(GoalVars0, IgnoreVarList, GoalVars),
+    set.delete_list(IgnoreVarList, GoalVars0, GoalVars),

      GoalVarList = set.to_sorted_list(GoalVars),

      GoalNonLocalSet0 = goal_info_get_nonlocals(GoalInfo),
-    set.delete_list(GoalNonLocalSet0, IgnoreVarList, GoalNonLocalSet),
+    set.delete_list(IgnoreVarList, GoalNonLocalSet0, GoalNonLocalSet),
      GoalNonLocals = set.to_sorted_list(GoalNonLocalSet),

      order_vars_into_groups(ModuleInfo, GoalVarList, InitInstmap, FinalInstmap,
@@ -2175,15 +2175,16 @@
          ModuleInfo, InstmapDelta),
      HldsGoalExpr = unify(VarLHS, UnifyRHS, UnifyMode, UnifyType, UnifyContext),

-    set.init(NonLocals0),
-    set.insert(NonLocals0, VarLHS, NonLocals1),
-    set.insert(NonLocals1, VarRHS, NonLocals),
-
-    Determism = detism_semi,
-    Purity = purity_pure,
-    goal_info_init(NonLocals, InstmapDelta, Determism, Purity, Context,
-        HldsGoalInfo),
-
+    some [!NonLocals] (
+        set.init(!:NonLocals),
+        set.insert(VarLHS, !NonLocals),
+        set.insert(VarRHS, !NonLocals),
+
+        Determism = detism_semi,
+        Purity = purity_pure,
+        goal_info_init(!.NonLocals, InstmapDelta, Determism, Purity, Context,
+            HldsGoalInfo)
+    ),
      HldsGoal = hlds_goal(HldsGoalExpr, HldsGoalInfo).

      % Creates a unification between two variables (using the unify goal)
@@ -2205,15 +2206,16 @@
          ModuleInfo, InstmapDelta),
      HldsGoalExpr = unify(VarLHS, UnifyRHS, UnifyMode, UnifyType, UnifyContext),

-    set.init(NonLocals0),
-    set.insert(NonLocals0, VarLHS, NonLocals1),
-    set.insert(NonLocals1, VarRHS, NonLocals),
-
-    Determism = detism_det,
-    Purity = purity_pure,
-    goal_info_init(NonLocals, InstmapDelta, Determism, Purity, Context,
-        HldsGoalInfo),
-
+    some [!NonLocals] (
+        set.init(!:NonLocals),
+        set.insert(VarLHS, !NonLocals),
+        set.insert(VarRHS, !NonLocals),
+
+        Determism = detism_det,
+        Purity = purity_pure,
+        goal_info_init(!.NonLocals, InstmapDelta, Determism, Purity, Context,
+            HldsGoalInfo)
+    ),
      HldsGoal = hlds_goal(HldsGoalExpr, HldsGoalInfo).

      % Creates a unification between two variables (using the unify goal)
@@ -2234,15 +2236,16 @@
          ModuleInfo, InstmapDelta),
      HldsGoalExpr = unify(VarLHS, UnifyRHS, UnifyMode, UnifyType, UnifyContext),

-    set.init(NonLocals0),
-    set.insert(NonLocals0, VarLHS, NonLocals1),
-    set.insert(NonLocals1, VarRHS, NonLocals),
-
-    Determism = detism_det,
-    Purity = purity_pure,
-    goal_info_init(NonLocals, InstmapDelta, Determism, Purity, Context,
-        HldsGoalInfo),
-
+    some [!NonLocals] (
+        set.init(!:NonLocals),
+        set.insert(VarLHS, !NonLocals),
+        set.insert(VarRHS, !NonLocals),
+
+        Determism = detism_det,
+        Purity = purity_pure,
+        goal_info_init(!.NonLocals, InstmapDelta, Determism, Purity, Context,
+            HldsGoalInfo)
+    ),
      HldsGoal = hlds_goal(HldsGoalExpr, HldsGoalInfo).

      % Creates a simple call.  If the call is polymorphic, remember to add
@@ -2456,7 +2459,7 @@
          NewPredName),

      set.init(CallNonLocals0),
-    set.insert_list(CallNonLocals0, ProcHeadVars, CallNonLocals),
+    set.insert_list(ProcHeadVars, CallNonLocals0, CallNonLocals),
      instmap_delta_from_mode_list(ProcHeadVars, ProcHeadModes, ModuleInfo0,
          CallInstmapDelta),

Index: compiler/store_alloc.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/store_alloc.m,v
retrieving revision 1.114
diff -u -r1.114 store_alloc.m
--- compiler/store_alloc.m	3 May 2011 04:34:58 -0000	1.114
+++ compiler/store_alloc.m	5 May 2011 12:21:44 -0000
@@ -244,7 +244,7 @@
          GoalExpr0 = scope(Reason, SubGoal0),
          ( Reason = from_ground_term(TermVar, from_ground_term_construct) ->
              GoalExpr = GoalExpr0,
-            set.insert(!.Liveness, TermVar, !:Liveness)
+            set.insert(TermVar, !Liveness)
          ;
              store_alloc_in_goal(SubGoal0, SubGoal, !Liveness, !LastLocns,
                  ResumeVars0, StoreAllocInfo),
@@ -426,7 +426,7 @@
      ;
          FinalLocn = Locn
      ),
-    set.insert(!.SeenLocns, FinalLocn, !:SeenLocns),
+    set.insert(FinalLocn, !SeenLocns),
      store_alloc_handle_conflicts_and_nonreal(Vars, !N, !SeenLocns,
          !StoreMap).

@@ -458,7 +458,7 @@
              Locn = abs_reg(!.N)
          ),
          map.det_insert(Var, Locn, !StoreMap),
-        set.insert(!.SeenLocns, Locn, !:SeenLocns)
+        set.insert(Locn, !SeenLocns)
      ),
      store_alloc_allocate_extras(Vars, !.N, !.SeenLocns, StoreAllocInfo,
          !StoreMap).
Index: compiler/stratify.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/stratify.m,v
retrieving revision 1.77
diff -u -r1.77 stratify.m
--- compiler/stratify.m	3 May 2011 04:34:58 -0000	1.77
+++ compiler/stratify.m	5 May 2011 10:54:21 -0000
@@ -685,7 +685,7 @@
      map.det_insert(PredProcId, ho_info(HaveAT, HOInOut), !HOInfo),
      (
          CallsHigherOrder = calls_higher_order,
-        set.insert(!.CallsHO, PredProcId, !:CallsHO)
+        set.insert(PredProcId, !CallsHO)
      ;
          CallsHigherOrder = does_not_calls_higher_order
      ).
@@ -770,7 +770,7 @@
                  _EvalMethod, _NonLocals, _Vars, _Modes, _Determinism,
                  LambdaGoal),
              get_called_procs(LambdaGoal, [], CalledProcs),
-            set.insert_list(!.HasAT, CalledProcs, !:HasAT)
+            set.insert_list(CalledProcs, !HasAT)
          ;
              RHS = rhs_var(_)
          ;
@@ -783,7 +783,7 @@
              Unification = construct(_, ConsId, _, _, _, _, _),
              ( ConsId = closure_cons(ShroudedPredProcId, _) ->
                  PredProcId = unshroud_pred_proc_id(ShroudedPredProcId),
-                set.insert(!.HasAT, PredProcId, !:HasAT)
+                set.insert(PredProcId, !HasAT)
              ;
                  % Do nothing.
                  true
@@ -801,7 +801,7 @@
      ;
          GoalExpr = plain_call(CPred, CProc, _Args, _Builtin, _UC, _Sym),
          % Add this call to the call list.
-        set.insert(!.Calls, proc(CPred, CProc), !:Calls)
+        set.insert(proc(CPred, CProc), !Calls)
      ;
          GoalExpr = call_foreign_proc(_Attrib, _CPred, _CProc, _, _, _, _)
          % Do nothing.
Index: compiler/structure_reuse.domain.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/structure_reuse.domain.m,v
retrieving revision 1.25
diff -u -r1.25 structure_reuse.domain.m
--- compiler/structure_reuse.domain.m	3 May 2011 04:34:58 -0000	1.25
+++ compiler/structure_reuse.domain.m	5 May 2011 13:46:29 -0000
@@ -281,7 +281,6 @@
  :- import_module set.
  :- import_module solutions.
  :- import_module string.
-:- import_module svset.

  %-----------------------------------------------------------------------------%

@@ -812,8 +811,8 @@
      set(prog_var)::in, set(prog_var)::out) is det.

  collect_aliased_vars(DataA - DataB, !Vars) :-
-    svset.insert(DataA ^ sc_var, !Vars),
-    svset.insert(DataB ^ sc_var, !Vars).
+    set.insert(DataA ^ sc_var, !Vars),
+    set.insert(DataB ^ sc_var, !Vars).

  %-----------------------------------------------------------------------------%

Index: compiler/structure_reuse.versions.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/structure_reuse.versions.m,v
retrieving revision 1.23
diff -u -r1.23 structure_reuse.versions.m
--- compiler/structure_reuse.versions.m	3 May 2011 04:31:19 -0000	1.23
+++ compiler/structure_reuse.versions.m	5 May 2011 13:00:36 -0000
@@ -199,7 +199,7 @@
      module_info_set_predicate_table(PredTable, !ModuleInfo),

      module_info_get_structure_reuse_preds(!.ModuleInfo, ReusePreds0),
-    set.insert(ReusePreds0, ReusePredId, ReusePreds),
+    set.insert(ReusePredId, ReusePreds0, ReusePreds),
      module_info_set_structure_reuse_preds(ReusePreds, !ModuleInfo).

  :- pred create_fresh_pred_proc_info_copy_2(pred_id::in, pred_info::in,
Index: compiler/structure_sharing.domain.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/structure_sharing.domain.m,v
retrieving revision 1.44
diff -u -r1.44 structure_sharing.domain.m
--- compiler/structure_sharing.domain.m	3 May 2011 04:34:58 -0000	1.44
+++ compiler/structure_sharing.domain.m	5 May 2011 13:46:36 -0000
@@ -317,7 +317,6 @@
  :- import_module require.
  :- import_module solutions.
  :- import_module string.
-:- import_module svset.
  :- import_module univ.
  :- import_module varset.

@@ -1457,7 +1456,7 @@
      SelSharingSet0 = selector_sharing_set(SelSize0, SelSharingMap0),
      map.lookup(SelSharingMap0, FromSel, DataSet0),
      DataSet0 = datastructures(DataSize0, Data0),
-    ( set.remove(Data0, ToData, Data) ->
+    ( set.remove(ToData, Data0, Data) ->
          DataSize = DataSize0 - 1,
          SelSize = SelSize0 - 1,
          Size = Size0 - 1,
@@ -2095,14 +2094,14 @@
  data_set_new_entry(Datastruct, DataSet0, DataSet) :-
      DataSet0 = datastructures(Size0, Datastructs0),
      \+ set.member(Datastruct, Datastructs0),
-    set.insert(Datastructs0, Datastruct, Datastructs),
+    set.insert(Datastruct, Datastructs0, Datastructs),
      Size = Size0 + 1,
      DataSet = datastructures(Size, Datastructs).

  data_set_delete_entry(Datastruct, DataSet0, DataSet) :-
      DataSet0 = datastructures(Size0, Datastructs0),
      ( set.contains(Datastructs0, Datastruct) ->
-        set.delete(Datastructs0, Datastruct, Datastructs),
+        set.delete(Datastruct, Datastructs0, Datastructs),
          Size = Size0 - 1,
          DataSet = datastructures(Size, Datastructs)
      ;
@@ -2160,7 +2159,7 @@
      ->
          true
      ;
-        svset.insert(Data, !Datastructs)
+        set.insert(Data, !Datastructs)
      ).

  data_set_apply_widening(ModuleInfo, ProcInfo, !DataSet):-
Index: compiler/superhomogeneous.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/superhomogeneous.m,v
retrieving revision 1.43
diff -u -r1.43 superhomogeneous.m
--- compiler/superhomogeneous.m	5 May 2011 03:58:56 -0000	1.43
+++ compiler/superhomogeneous.m	5 May 2011 13:46:47 -0000
@@ -140,7 +140,6 @@
  :- import_module pair.
  :- import_module require.
  :- import_module set.
-:- import_module svset.
  :- import_module term.
  :- import_module varset.

@@ -1075,8 +1074,8 @@
              % to the proper set of nonlocal arguments.
              some [!LambdaGoalVars] (
                  goal_util.goal_vars(HLDS_Goal, !:LambdaGoalVars),
-                svset.delete_list(LambdaVars, !LambdaGoalVars),
-                svset.delete_list(QuantifiedVars, !LambdaGoalVars),
+                set.delete_list(LambdaVars, !LambdaGoalVars),
+                set.delete_list(QuantifiedVars, !LambdaGoalVars),
                  LambdaNonLocals = set.to_sorted_list(!.LambdaGoalVars)
              ),

Index: compiler/switch_detection.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/switch_detection.m,v
retrieving revision 1.154
diff -u -r1.154 switch_detection.m
--- compiler/switch_detection.m	3 May 2011 04:34:59 -0000	1.154
+++ compiler/switch_detection.m	5 May 2011 10:56:17 -0000
@@ -784,7 +784,7 @@
                  % specific to each cons_id, so it could not be shared with
                  % other cons_ids.
                  NonLocals = goal_info_get_nonlocals(FirstGoalInfo),
-                set.delete(NonLocals, Var, OtherNonLocals),
+                set.delete(Var, NonLocals, OtherNonLocals),
                  set.empty(OtherNonLocals),

                  all_disjuncts_are_switch_var_unifies(Var, Disjuncts,
Index: compiler/switch_util.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/switch_util.m,v
retrieving revision 1.52
diff -u -r1.52 switch_util.m
--- compiler/switch_util.m	5 May 2011 06:39:36 -0000	1.52
+++ compiler/switch_util.m	5 May 2011 10:32:58 -0000
@@ -1234,7 +1234,7 @@
          unexpected(this_file, "non-du tag in group_case_by_ptag")
      ),
      ( map.search(!.CaseNumPtagsMap, CaseNum, Ptags0) ->
-        set.insert(Ptags0, Primary, Ptags),
+        set.insert(Primary, Ptags0, Ptags),
          map.det_update(CaseNum, Ptags, !CaseNumPtagsMap)
      ;
          Ptags = set.make_singleton_set(Primary),
Index: compiler/table_gen.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/table_gen.m,v
retrieving revision 1.161
diff -u -r1.161 table_gen.m
--- compiler/table_gen.m	5 May 2011 03:58:56 -0000	1.161
+++ compiler/table_gen.m	5 May 2011 13:29:12 -0000
@@ -746,7 +746,7 @@
          AfterGoal = hlds_goal(AfterGoalExpr, AfterGoalInfo),
          FirstGoalExpr = conj(plain_conj, [OrigGoal, AfterGoal]),
          OrigGINonLocals = goal_info_get_nonlocals(OrigGoalInfo),
-        set.insert(OrigGINonLocals, TableTipVar, FirstNonlocals),
+        set.insert(TableTipVar, OrigGINonLocals, FirstNonlocals),
          goal_info_set_nonlocals(FirstNonlocals, OrigGoalInfo, FirstGoalInfo),
          FirstGoal = hlds_goal(FirstGoalExpr, FirstGoalInfo),
          InactiveGoalExpr = disj([FirstGoal, MarkInactiveFailGoal])
@@ -760,8 +760,8 @@
          case(loop_inactive_cons_id, [], InactiveGoal)
      ],
      SwitchExpr = switch(StatusVar, cannot_fail, SwitchArms),
-    set.insert_list(InactiveNonLocals, [StatusVar, TableTipVar],
-        SwitchNonLocals),
+    set.insert_list([StatusVar, TableTipVar],
+        InactiveNonLocals, SwitchNonLocals),
      goal_info_init_hide(SwitchNonLocals, InactiveInstmapDelta, Detism,
          purity_impure, Context, SwitchGoalInfo),
      SwitchGoal = hlds_goal(SwitchExpr, SwitchGoalInfo),
@@ -1001,7 +1001,7 @@
      ),

      SwitchExpr = switch(StatusVar, cannot_fail, SwitchArms),
-    set.insert(InactiveNonLocals, StatusVar, SwitchNonLocals),
+    set.insert(StatusVar, InactiveNonLocals, SwitchNonLocals),
      goal_info_init_hide(SwitchNonLocals, InactiveInstmapDelta,
          Detism, purity_impure, Context, SwitchGoalInfo),
      SwitchGoal = hlds_goal(SwitchExpr, SwitchGoalInfo),
@@ -1085,7 +1085,7 @@
          ModuleInfo, Context, MarkCompleteGoal),

      OrigSaveExpr = conj(plain_conj, [OrigGoal | SaveAnswerGoals]),
-    set.insert(OrigNonLocals, RecordVar, OrigSaveNonLocals),
+    set.insert(RecordVar, OrigNonLocals, OrigSaveNonLocals),
      create_instmap_delta([OrigGoal | SaveAnswerGoals], OrigSaveIMD0),
      instmap_delta_restrict(OrigSaveNonLocals, OrigSaveIMD0, OrigSaveIMD),
      goal_info_init_hide(OrigSaveNonLocals, OrigSaveIMD, detism_non,
@@ -1117,7 +1117,7 @@
      ],

      SwitchExpr = switch(StatusVar, cannot_fail, SwitchArms),
-    set.insert(InactiveNonLocals, StatusVar, SwitchNonLocals),
+    set.insert(StatusVar, InactiveNonLocals, SwitchNonLocals),
      goal_info_init_hide(SwitchNonLocals, InactiveInstmapDelta, Detism,
          purity_impure, Context, SwitchGoalInfo),
      SwitchGoal = hlds_goal(SwitchExpr, SwitchGoalInfo),
@@ -1330,9 +1330,8 @@
          RestoreAnswerGoal0 = hlds_goal(_, RestoreAnswerGoal0Info),
          RestoreAnswer0NonLocals =
              goal_info_get_nonlocals(RestoreAnswerGoal0Info),
-        set.insert_list(RestoreAnswer0NonLocals,
-            [IoStateAssignFromVar, IoStateAssignToVar],
-            RestoreAnswerNonLocals),
+        set.insert_list([IoStateAssignFromVar, IoStateAssignToVar],
+            RestoreAnswer0NonLocals, RestoreAnswerNonLocals),
          instmap_delta_restrict(RestoreAnswerNonLocals,
              RestoreAnswerInstMapDelta0, RestoreAnswerInstMapDelta),
          goal_info_init_hide(RestoreAnswerNonLocals,
@@ -1362,7 +1361,7 @@
      ),
      CallSaveAnswerGoalExpr = conj(plain_conj, CallSaveAnswerGoalList),
      create_instmap_delta(CallSaveAnswerGoalList, CallSaveAnswerInstMapDelta0),
-    set.insert(OrigNonLocals, TipVar, CallSaveAnswerNonLocals),
+    set.insert(TipVar, OrigNonLocals, CallSaveAnswerNonLocals),
      instmap_delta_restrict(CallSaveAnswerNonLocals,
          CallSaveAnswerInstMapDelta0, CallSaveAnswerInstMapDelta),
      goal_info_init_hide(CallSaveAnswerNonLocals, CallSaveAnswerInstMapDelta,
@@ -1376,7 +1375,7 @@
          RestoreAnswerGoal, CallSaveAnswerGoal),
      create_instmap_delta([OccurredGoal, RestoreAnswerGoal,
          CallSaveAnswerGoal], GenIfNecInstMapDelta0),
-    set.insert(OrigNonLocals, TipVar, GenIfNecNonLocals),
+    set.insert(TipVar, OrigNonLocals, GenIfNecNonLocals),
      instmap_delta_restrict(GenIfNecNonLocals,
          GenIfNecInstMapDelta0, GenIfNecInstMapDelta),
      goal_info_init_hide(GenIfNecNonLocals, GenIfNecInstMapDelta, detism_det,
@@ -1386,8 +1385,8 @@
      CheckAndGenAnswerGoalExpr = conj(plain_conj, [LookupGoal, GenIfNecGoal]),
      create_instmap_delta([LookupGoal, GenIfNecGoal],
          CheckAndGenAnswerInstMapDelta0),
-    set.insert_list(OrigNonLocals, [TableVar, CounterVar, StartVar],
-        CheckAndGenAnswerNonLocals),
+    set.insert_list([TableVar, CounterVar, StartVar],
+        OrigNonLocals, CheckAndGenAnswerNonLocals),
      instmap_delta_restrict(CheckAndGenAnswerNonLocals,
          CheckAndGenAnswerInstMapDelta0, CheckAndGenAnswerInstMapDelta),
      goal_info_init_hide(CheckAndGenAnswerNonLocals,
@@ -1492,7 +1491,7 @@
          SubgoalVar, Context, !VarSet, !VarTypes, !.TableInfo, SuspendGoal),

      MainExpr = conj(plain_conj, [OrigGoal | SaveAnswerGoals]),
-    set.insert_list(OrigNonLocals, [SubgoalVar, StatusVar], MainNonLocals),
+    set.insert_list([SubgoalVar, StatusVar], OrigNonLocals, MainNonLocals),
      create_instmap_delta([OrigGoal | SaveAnswerGoals], MainIMD0),
      instmap_delta_restrict(MainNonLocals, MainIMD0, MainIMD),
      goal_info_init_hide(MainNonLocals, MainIMD, detism_non, purity_impure,
@@ -1792,7 +1791,7 @@

      MainGoalExpr = conj(plain_conj, [OrigGoal | SaveReturnAnswerGoals]),
      Detism = goal_info_get_determinism(OrigGoalInfo),
-    set.insert(OrigNonLocals, GeneratorVar, NonLocals),
+    set.insert(GeneratorVar, OrigNonLocals, NonLocals),
      goal_info_init(NonLocals, OrigInstMapDelta, Detism, purity_impure, Context,
          MainGoalInfo0),
      goal_info_add_feature(feature_hide_debug_event,
@@ -2298,7 +2297,7 @@
  attach_call_table_tip(hlds_goal(GoalExpr, GoalInfo0),
          hlds_goal(GoalExpr, GoalInfo)) :-
      Features0 = goal_info_get_features(GoalInfo0),
-    set.insert(Features0, feature_call_table_gen, Features),
+    set.insert(feature_call_table_gen, Features0, Features),
      goal_info_set_features(Features, GoalInfo0, GoalInfo).

  %-----------------------------------------------------------------------------%
Index: compiler/term_pass1.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/term_pass1.m,v
retrieving revision 1.44
diff -u -r1.44 term_pass1.m
--- compiler/term_pass1.m	5 May 2011 03:58:57 -0000	1.44
+++ compiler/term_pass1.m	5 May 2011 13:46:52 -0000
@@ -68,7 +68,6 @@
  :- import_module maybe.
  :- import_module require.
  :- import_module set.
-:- import_module svset.
  :- import_module term.
  :- import_module varset.

@@ -454,7 +453,7 @@
          Coeff = Var - (-1.0)
      ),
      list.map_foldl2(Convert, PPIds, RestCoeffs, !Varset, !PPVars),
-    svset.insert(Eqn, !Eqns),
+    set.insert(Eqn, !Eqns),
      convert_equations_2(Paths, !PPVars, !Varset, !Eqns).

  :- pred lookup_coeff(map(pred_proc_id, var)::in, map(var, float)::in,
Index: compiler/term_traversal.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/term_traversal.m,v
retrieving revision 1.64
diff -u -r1.64 term_traversal.m
--- compiler/term_traversal.m	3 May 2011 14:22:14 -0000	1.64
+++ compiler/term_traversal.m	5 May 2011 13:47:00 -0000
@@ -115,7 +115,6 @@
  :- import_module int.
  :- import_module map.
  :- import_module require.
-:- import_module svset.

  %-----------------------------------------------------------------------------%

@@ -401,7 +400,7 @@
          Info = Info0
      ;
          Info0 = term_traversal_ok(Paths0, CanLoop),
-        set.insert(Paths0, Path, Paths),
+        set.insert(Path, Paths0, Paths),
          Info = term_traversal_ok(Paths, CanLoop)
      ).

@@ -587,7 +586,7 @@
          % The change produces no active variables.
          Path = Path0
      ),
-    svset.insert(Path, !PathSet),
+    set.insert(Path, !PathSet),
      record_change_2(Paths0, InVars, OutVars, CallGamma, CallPPIds, !PathSet).

  %-----------------------------------------------------------------------------%
Index: compiler/trace_gen.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/trace_gen.m,v
retrieving revision 1.35
diff -u -r1.35 trace_gen.m
--- compiler/trace_gen.m	27 Jan 2011 08:03:52 -0000	1.35
+++ compiler/trace_gen.m	5 May 2011 12:22:06 -0000
@@ -1227,7 +1227,7 @@
      LiveType = live_value_var(Var, Name, Type, LldsInst),
      VarInfo = layout_var_info(locn_direct(Lval), LiveType, "trace"),
      type_vars(Type, TypeVars),
-    set.insert_list(!.Tvars, TypeVars, !:Tvars).
+    set.insert_list(TypeVars, !Tvars).

  %-----------------------------------------------------------------------------%

Index: compiler/try_expand.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/try_expand.m,v
retrieving revision 1.15
diff -u -r1.15 try_expand.m
--- compiler/try_expand.m	3 May 2011 04:34:59 -0000	1.15
+++ compiler/try_expand.m	5 May 2011 10:58:29 -0000
@@ -501,7 +501,7 @@
          GoalOutputVarsSet0),
      (
          MaybeIO = yes(try_io_state_vars(_IOStateVarInitial, IOStateVarFinal)),
-        set.delete(GoalOutputVarsSet0, IOStateVarFinal, GoalOutputVarsSet)
+        set.delete(IOStateVarFinal, GoalOutputVarsSet0, GoalOutputVarsSet)
      ;
          MaybeIO = no,
          GoalOutputVarsSet = GoalOutputVarsSet0
@@ -808,7 +808,7 @@
          LambdaParams = [OutputTupleVar, IOVarInitial, IOVarFinal],
          LambdaParamTypes = [OutputTupleType, io_state_type, io_state_type],
          LambdaParamModes = [out_mode, di_mode, uo_mode],
-        set.delete(NonLocals1, IOVarFinal, NonLocals)
+        set.delete(IOVarFinal, NonLocals1, NonLocals)
      ;
          MaybeIO = no,
          LambdaParams = [OutputTupleVar],
Index: compiler/tupling.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/tupling.m,v
retrieving revision 1.59
diff -u -r1.59 tupling.m
--- compiler/tupling.m	5 May 2011 06:39:36 -0000	1.59
+++ compiler/tupling.m	5 May 2011 13:32:53 -0000
@@ -1217,7 +1217,7 @@
          % In this case, the cell var is not being used to access field
          % variables, so it should not incur the cell var cost.
          cls_require_normal_var_in_reg(CountInfo, CellVar, !CountState),
-        set.delete_list(InputArgs0, FieldVars, InputArgs)
+        set.delete_list(FieldVars, InputArgs0, InputArgs)
      ;
          % The cell var cannot be used for the callee, so we must add
          % the cost of constructing a new tuple.
@@ -1386,10 +1386,10 @@
          CvLoadCost = float(TuningParams ^ tp_cell_var_load_cost),
          FvLoadCost = float(TuningParams ^ tp_field_var_load_cost),
          ( set.member(CellVar, RegVars0) ->
-            set.insert(RegVars0, FieldVar, RegVars),
+            set.insert(FieldVar, RegVars0, RegVars),
              Loads = Loads0 + FvLoadCost
          ;
-            set.insert_list(RegVars0, [CellVar, FieldVar], RegVars),
+            set.insert_list([CellVar, FieldVar], RegVars0, RegVars),
              Loads = Loads0 + CvLoadCost + FvLoadCost
          ),
          CountState = count_state(RegVars, StackVars, Loads, Stores)
@@ -1403,7 +1403,7 @@
      ( set.member(Var, RegVars0) ->
          CountState = CountState0
      ;
-        set.insert(RegVars0, Var, RegVars),
+        set.insert(Var, RegVars0, RegVars),
          Loads = Loads0 + float(LoadCost),
          CountState = count_state(RegVars, StackVars, Loads, Stores)
      ).
@@ -1415,7 +1415,7 @@

  cls_put_in_regs(Vars, !CountState) :-
      RegVars0 = !.CountState ^ cs_reg_vars,
-    set.insert_list(RegVars0, Vars, RegVars),
+    set.insert_list(Vars, RegVars0, RegVars),
      !CountState ^ cs_reg_vars := RegVars.

  :- pred cls_put_in_regs_via_deconstruct(count_info::in, prog_var::in,
Index: compiler/type_constraints.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/type_constraints.m,v
retrieving revision 1.16
diff -u -r1.16 type_constraints.m
--- compiler/type_constraints.m	5 May 2011 06:39:36 -0000	1.16
+++ compiler/type_constraints.m	5 May 2011 13:47:07 -0000
@@ -62,7 +62,6 @@
  :- import_module require.
  :- import_module set.
  :- import_module string.
-:- import_module svset.
  :- import_module term.
  :- import_module term_io.
  :- import_module varset.
@@ -931,7 +930,7 @@
          % those variables.
          list.foldl(update_replacement_map(VarMap, Replacement), UnifiedVars,
              !ReplacementMap),
-        svset.insert_list(UnifiedVars, Replaced, Replaced1),
+        set.insert_list(UnifiedVars, Replaced, Replaced1),
          list.foldl2(unify_equal_tvars(TCInfo, Replaced1, Replacement),
              UnifiedVars, !ReplacementMap, !DomainMap)
      ;
@@ -1510,7 +1509,7 @@
      TCInfo = tconstr_info(VarMap, _, ConstraintMap, VarConstraints,
          TVarSet, _),
      map.lookup(VarConstraints, TypeVar, ConstraintIds),
-    svset.insert_list(ConstraintIds, set.init, ConstraintSet),
+    set.insert_list(ConstraintIds, set.init, ConstraintSet),
      min_unsat_constraints(TCInfo, set.init, ConstraintSet, [], MinUnsats),
      list.map(error_from_one_min_set(ConstraintMap), MinUnsats, MinUnsatPieces),
      zip_single([suffix(") or"), nl, prefix("(")],
@@ -1588,9 +1587,9 @@
      list(type_constraint_set)::in, list(type_constraint_set)::out) is det.

  next_min_unsat(Constraint, C, !D, !P, !MinUnsats) :-
-    svset.delete(C, !P),
+    set.delete(C, !P),
      min_unsat_constraints(Constraint, !.D, !.P, !MinUnsats),
-    svset.insert(C, !D).
+    set.insert(C, !D).

  :- pred add_message_to_spec(error_msg::in, type_constraint_info::in,
      type_constraint_info::out) is det.
Index: compiler/type_ctor_info.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/type_ctor_info.m,v
retrieving revision 1.105
diff -u -r1.105 type_ctor_info.m
--- compiler/type_ctor_info.m	5 May 2011 06:39:36 -0000	1.105
+++ compiler/type_ctor_info.m	5 May 2011 13:47:15 -0000
@@ -93,7 +93,6 @@
  :- import_module require.
  :- import_module set.
  :- import_module string.
-:- import_module svset.
  :- import_module term.
  :- import_module univ.
  :- import_module varset.
@@ -411,10 +410,10 @@
          !:Flags = set.init,
          (
              TypeBody = hlds_du_type(_, _, _, _, _, BodyReservedTag, _, _),
-            svset.insert(kind_of_du_flag, !Flags),
+            set.insert(kind_of_du_flag, !Flags),
              (
                  BodyReservedTag = uses_reserved_tag,
-                svset.insert(reserve_tag_flag, !Flags)
+                set.insert(reserve_tag_flag, !Flags)
              ;
                  BodyReservedTag = does_not_use_reserved_tag
              )
Index: compiler/type_util.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/type_util.m,v
retrieving revision 1.205
diff -u -r1.205 type_util.m
--- compiler/type_util.m	3 May 2011 04:34:59 -0000	1.205
+++ compiler/type_util.m	5 May 2011 13:36:22 -0000
@@ -362,7 +362,6 @@
  :- import_module map.
  :- import_module require.
  :- import_module set.
-:- import_module svset.
  :- import_module term.

  %-----------------------------------------------------------------------------%
@@ -452,7 +451,7 @@
          % Don't loop on recursive types.
          true
      else
-        svset.insert(Type, !SeenTypes),
+        set.insert(Type, !SeenTypes),
          (
              Type = builtin_type(_)
          ;
Index: compiler/typecheck_info.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/typecheck_info.m,v
retrieving revision 1.34
diff -u -r1.34 typecheck_info.m
--- compiler/typecheck_info.m	3 May 2011 04:34:59 -0000	1.34
+++ compiler/typecheck_info.m	5 May 2011 10:59:00 -0000
@@ -535,7 +535,7 @@
  expand_types(TypeSubst, _Var, Type0, Type, !TypeVarsSet) :-
      apply_rec_subst_to_type(TypeSubst, Type0, Type),
      type_vars(Type, TypeVars),
-    set.insert_list(!.TypeVarsSet, TypeVars, !:TypeVarsSet).
+    set.insert_list(TypeVars, !TypeVarsSet).

      % We rename any existentially quantified type variables which get mapped
      % to other type variables, unless they are mapped to universally quantified
Index: compiler/unused_args.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/unused_args.m,v
retrieving revision 1.167
diff -u -r1.167 unused_args.m
--- compiler/unused_args.m	5 May 2011 03:58:57 -0000	1.167
+++ compiler/unused_args.m	5 May 2011 13:35:14 -0000
@@ -578,7 +578,7 @@
  add_aliases(Var, Aliases, !VarDep) :-
      ( map.search(!.VarDep, Var, VarInf0) ->
          VarInf0 = unused(VarDep0, ArgDep),
-        set.insert_list(VarDep0, Aliases, VarDep),
+        set.insert_list(Aliases, VarDep0, VarDep),
          VarInf = unused(VarDep, ArgDep),
          map.det_update(Var, VarInf, !VarDep)
      ;
@@ -763,7 +763,7 @@
  add_arg_dep(Var, PredProc, Arg, !VarDep) :-
      ( lookup_local_var(!.VarDep, Var, VarUsage0) ->
          VarUsage0 = unused(VarDep, ArgDep0),
-        set.insert(ArgDep0, arg_var_in_proc(PredProc, Arg), ArgDep),
+        set.insert(arg_var_in_proc(PredProc, Arg), ArgDep0, ArgDep),
          VarUsage = unused(VarDep, ArgDep),
          map.det_update(Var, VarUsage, !VarDep)
      ;
@@ -832,7 +832,7 @@
  add_construction_aliases(Alias, [Var | Vars], !VarDep) :-
      ( lookup_local_var(!.VarDep, Var, VarInfo0) ->
          VarInfo0 = unused(VarDep0, ArgDep),
-        set.insert(VarDep0, Alias, VarDep),
+        set.insert(Alias, VarDep0, VarDep),
          VarInfo = unused(VarDep, ArgDep),
          map.set(Var, VarInfo, !VarDep)
      ;
@@ -1804,7 +1804,7 @@
      ( set.member(PredId, !.WarnedPredIds) ->
          true
      ;
-        set.insert(!.WarnedPredIds, PredId, !:WarnedPredIds),
+        set.insert(PredId, !WarnedPredIds),
          pred_info_get_procedures(PredInfo, Procs),
          map.lookup(Procs, ProcId, Proc),
          proc_info_get_headvars(Proc, HeadVars),
Index: compiler/use_local_vars.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/use_local_vars.m,v
retrieving revision 1.44
diff -u -r1.44 use_local_vars.m
--- compiler/use_local_vars.m	3 May 2011 04:34:59 -0000	1.44
+++ compiler/use_local_vars.m	5 May 2011 12:22:41 -0000
@@ -404,7 +404,7 @@
              this_file, "opt_access: nonempty SubChosenLvals"),
          substitute_lval_in_instr_until_defn(ChosenLval, TempLval,
              [Instr0 | TailInstrs0], Instrs1, 0, NumReplacements),
-        set.insert(AlreadyTried0, ChosenLval, AlreadyTried1),
+        set.insert(ChosenLval, AlreadyTried0, AlreadyTried1),
          ( NumReplacements >= AccessThreshold ->
              TempAssign = llds_instr(assign(TempLval, lval(ChosenLval)),
                  "factor out common sub lval"),
Index: compiler/var_locn.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/var_locn.m,v
retrieving revision 1.73
diff -u -r1.73 var_locn.m
--- compiler/var_locn.m	3 May 2011 04:34:59 -0000	1.73
+++ compiler/var_locn.m	5 May 2011 12:31:27 -0000
@@ -681,7 +681,7 @@
          MaybeExprRval = yes(_),
          State = var_state(Lvals, MaybeConstRval, yes(var(OldVar)), set.init,
              doa_alive),
-        set.insert(Using0, Var, Using),
+        set.insert(Var, Using0, Using),
          OldState = var_state(Lvals, MaybeConstRval, MaybeExprRval, Using,
              DeadOrAlive),
          map.det_update(OldVar, OldState, VarStateMap0, VarStateMap1)
@@ -802,7 +802,7 @@
      map.lookup(!.VarStateMap, ContainedVar, State0),
      State0 = var_state(Lvals, MaybeConstRval, MaybeExprRval, Using0,
          DeadOrAlive),
-    set.insert(Using0, UsingVar, Using),
+    set.insert(UsingVar, Using0, Using),
      State = var_state(Lvals, MaybeConstRval, MaybeExprRval, Using,
          DeadOrAlive),
      map.det_update(ContainedVar, State, !VarStateMap).
@@ -1184,7 +1184,7 @@
      map.lookup(VarStateMap0, Var, State0),
      State0 = var_state(LvalSet0, MaybeConstRval, MaybeExprRval0,
          Using, DeadOrAlive),
-    set.insert(LvalSet0, Lval, LvalSet),
+    set.insert(Lval, LvalSet0, LvalSet),
      State = var_state(LvalSet, MaybeConstRval, no, Using, DeadOrAlive),
      map.det_update(Var, State, VarStateMap0, VarStateMap),
      var_locn_set_var_state_map(VarStateMap, !VLI),
@@ -1213,7 +1213,7 @@
      map.lookup(VarStateMap0, ContainedVar, State0),
      State0 = var_state(Lvals, MaybeConstRval, MaybeExprRval, Using0,
          DeadOrAlive),
-    ( set.remove(Using0, UsingVar, Using1) ->
+    ( set.remove(UsingVar, Using0, Using1) ->
          Using = Using1
      ;
          unexpected(this_file, "remove_use_refs_2: using ref not present")
@@ -1512,7 +1512,7 @@
      (
          var_locn_get_loc_var_map(!.VLI, LocVarMap0),
          map.search(LocVarMap0, Lval, AffectedVarSet),
-        set.delete_list(AffectedVarSet, ToBeAssignedVars, EffAffectedVarSet),
+        set.delete_list(ToBeAssignedVars, AffectedVarSet, EffAffectedVarSet),
          set.to_sorted_list(EffAffectedVarSet, EffAffectedVars),

          var_locn_get_var_state_map(!.VLI, VarStateMap0),
@@ -1576,7 +1576,7 @@
      State = var_state(LvalSet, _, _, _, _),
      ( set.member(Lval, LvalSet) ->
          OccupyingVar = Var,
-        set.delete(LvalSet, Lval, OtherSourceSet),
+        set.delete(Lval, LvalSet, OtherSourceSet),
          set.to_sorted_list(OtherSourceSet, OtherSources)
      ;
          find_one_occupying_var(Vars, Lval, VarStateMap, OccupyingVar,
@@ -1611,7 +1611,7 @@
  ensure_copies_are_present_lval([OtherSource | OtherSources], OneSource, Lval,
          !LvalSet) :-
      SubstLval = substitute_lval_in_lval(OneSource, OtherSource, Lval),
-    set.insert(!.LvalSet, SubstLval, !:LvalSet),
+    set.insert(SubstLval, !LvalSet),
      ensure_copies_are_present_lval(OtherSources, OneSource, Lval, !LvalSet).

  %----------------------------------------------------------------------------%
@@ -2027,7 +2027,7 @@
  var_locn_acquire_reg(Lval, !VLI) :-
      get_spare_reg(!.VLI, Lval),
      var_locn_get_acquired(!.VLI, Acquired0),
-    set.insert(Acquired0, Lval, Acquired),
+    set.insert(Lval, Acquired0, Acquired),
      var_locn_set_acquired(Acquired, !VLI).

  var_locn_acquire_reg_require_given(Lval, !VLI) :-
@@ -2037,7 +2037,7 @@
          true
      ),
      var_locn_get_acquired(!.VLI, Acquired0),
-    set.insert(Acquired0, Lval, Acquired),
+    set.insert(Lval, Acquired0, Acquired),
      var_locn_set_acquired(Acquired, !VLI).

  var_locn_acquire_reg_prefer_given(Pref, Lval, !VLI) :-
@@ -2048,7 +2048,7 @@
          Lval = PrefLval
      ),
      var_locn_get_acquired(!.VLI, Acquired0),
-    set.insert(Acquired0, Lval, Acquired),
+    set.insert(Lval, Acquired0, Acquired),
      var_locn_set_acquired(Acquired, !VLI).

  var_locn_acquire_reg_start_at_given(Start, Lval, !VLI) :-
@@ -2058,14 +2058,14 @@
      ;
          Lval = StartLval,
          var_locn_get_acquired(!.VLI, Acquired0),
-        set.insert(Acquired0, Lval, Acquired),
+        set.insert(Lval, Acquired0, Acquired),
          var_locn_set_acquired(Acquired, !VLI)
      ).

  var_locn_release_reg(Lval, !VLI) :-
      var_locn_get_acquired(!.VLI, Acquired0),
      ( set.member(Lval, Acquired0) ->
-        set.delete(Acquired0, Lval, Acquired),
+        set.delete(Lval, Acquired0, Acquired),
          var_locn_set_acquired(Acquired, !VLI)
      ;
          unexpected(this_file, "release_reg: unacquired reg")
@@ -2368,7 +2368,7 @@
      expect(is_root_lval(Lval),
          this_file, "make_var_depend_on_root_lval: non-root lval"),
      ( map.search(!.LocVarMap, Lval, Vars0) ->
-        set.insert(Vars0, Var, Vars),
+        set.insert(Var, Vars0, Vars),
          map.det_update(Lval, Vars, !LocVarMap)
      ;
          set.singleton_set(Vars, Var),
@@ -2385,7 +2385,7 @@
      expect(is_root_lval(Lval), this_file,
          "make_var_depend_on_root_lval: non-root lval"),
      ( map.search(!.LocVarMap, Lval, Vars0) ->
-        set.delete(Vars0, Var, Vars),
+        set.delete(Var, Vars0, Vars),
          ( set.empty(Vars) ->
              map.det_remove(Lval, _, !LocVarMap)
          ;
Index: compiler/write_deps_file.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/write_deps_file.m,v
retrieving revision 1.12
diff -u -r1.12 write_deps_file.m
--- compiler/write_deps_file.m	15 Dec 2010 06:30:10 -0000	1.12
+++ compiler/write_deps_file.m	5 May 2011 12:43:47 -0000
@@ -141,10 +141,10 @@
          list.append(IntDeps, ImplDeps, LongDeps0),
          ShortDeps0 = IndirectDeps,
          set.list_to_set(LongDeps0, LongDepsSet0),
-        set.delete(LongDepsSet0, ModuleName, LongDepsSet),
+        set.delete(ModuleName, LongDepsSet0, LongDepsSet),
          set.list_to_set(ShortDeps0, ShortDepsSet0),
          set.difference(ShortDepsSet0, LongDepsSet, ShortDepsSet1),
-        set.delete(ShortDepsSet1, ModuleName, ShortDepsSet),
+        set.delete(ModuleName, ShortDepsSet1, ShortDepsSet),
          set.to_sorted_list(LongDepsSet, LongDeps),
          set.to_sorted_list(ShortDepsSet, ShortDeps),
          set.to_sorted_list(AllDepsSet, AllDeps),
Index: deep_profiler/autopar_annotate.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/autopar_annotate.m,v
retrieving revision 1.2
diff -u -r1.2 autopar_annotate.m
--- deep_profiler/autopar_annotate.m	27 Jan 2011 08:03:53 -0000	1.2
+++ deep_profiler/autopar_annotate.m	5 May 2011 13:57:52 -0000
@@ -70,7 +70,7 @@
          GoalExpr = switch_rep(Var, _CanFail, Cases),
          switch_annotate_with_instmap(Cases, SeenDuplicateInstantiation,
              ConsumedVars0, BoundVars, !InstMap, !InstMapArray),
-        set.insert(ConsumedVars0, Var, ConsumedVars)
+        set.insert(Var, ConsumedVars0, ConsumedVars)
      ;
          GoalExpr = ite_rep(Cond, Then, Else),
          ite_annotate_with_instmap(Cond, Then, Else,
Index: deep_profiler/autopar_find_best_par.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/autopar_find_best_par.m,v
retrieving revision 1.4
diff -u -r1.4 autopar_find_best_par.m
--- deep_profiler/autopar_find_best_par.m	3 May 2011 04:35:00 -0000	1.4
+++ deep_profiler/autopar_find_best_par.m	5 May 2011 13:58:15 -0000
@@ -412,7 +412,7 @@
          io.flush_output(!IO)
      ),

-    ( set.remove_least(Solutions, BestParallelisation, _) ->
+    ( set.remove_least(BestParallelisation, Solutions, _) ->
          MaybeBestParallelisation = yes(BestParallelisation)
      ;
          % Solutions is empty.
Index: deep_profiler/autopar_search_callgraph.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/autopar_search_callgraph.m,v
retrieving revision 1.5
diff -u -r1.5 autopar_search_callgraph.m
--- deep_profiler/autopar_search_callgraph.m	5 May 2011 06:39:37 -0000	1.5
+++ deep_profiler/autopar_search_callgraph.m	5 May 2011 13:58:46 -0000
@@ -501,8 +501,8 @@
              Lo = OldLo,
              Hi = OldHi
          ->
-            set.insert_list(OldTargetGoalPathStrSet, TargetGoalPathStrs,
-                NewTargetGoalPathStrSet),
+            set.insert_list(TargetGoalPathStrs,
+                OldTargetGoalPathStrSet, NewTargetGoalPathStrSet),
              NewTriple = {OldLo, OldHi, NewTargetGoalPathStrSet},
              map.det_update(GoalPathStr, NewTriple, !Map)
          ;
Index: deep_profiler/canonical.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/canonical.m,v
retrieving revision 1.23
diff -u -r1.23 canonical.m
--- deep_profiler/canonical.m	5 May 2011 07:11:52 -0000	1.23
+++ deep_profiler/canonical.m	5 May 2011 13:54:25 -0000
@@ -114,8 +114,8 @@

  :- pred insert_pds(list(T)::in, set(T)::in, set(T)::out) is det.

-insert_pds(List, Set0, Set) :-
-    set.insert_list(Set0, List, Set).
+insert_pds(List, !Set) :-
+    set.insert_list(List, !Set).

      % find set of proc_statics in the CliquePDs
      % for all (first order) calls in CliquePDs, if call is to a procedure
@@ -482,7 +482,7 @@
          lookup_clique_index(MergeInfo ^ merge_clique_index, PDPtr, CliquePtr),
          lookup_clique_members(MergeInfo ^ merge_clique_members, CliquePtr,
              Members),
-        set.insert_list(!.CliqueUnion, Members, !:CliqueUnion)
+        set.insert_list(Members, !CliqueUnion)
      ).

  :- pred lookup_normal_sites(list(array(call_site_array_slot))::in, int::in,
Index: deep_profiler/cliques.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/cliques.m,v
retrieving revision 1.11
diff -u -r1.11 cliques.m
--- deep_profiler/cliques.m	4 Aug 2010 02:25:01 -0000	1.11
+++ deep_profiler/cliques.m	5 May 2011 13:54:42 -0000
@@ -72,7 +72,7 @@
  add_arc(graph(Size0, Array0), From, To, Graph) :-
      ( array.in_bounds(Array0, From) ->
          array.lookup(Array0, From, Tos0),
-        set.insert(Tos0, To, Tos),
+        set.insert(To, Tos0, Tos),
          array.set(u(Array0), From, Tos, Array),
          Size = int.max(int.max(From, To), Size0),
          Graph = graph(Size, Array)
Index: deep_profiler/html_format.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/html_format.m,v
retrieving revision 1.39
diff -u -r1.39 html_format.m
--- deep_profiler/html_format.m	5 May 2011 06:39:37 -0000	1.39
+++ deep_profiler/html_format.m	5 May 2011 13:55:12 -0000
@@ -426,7 +426,7 @@
      ( set.member(ColumnClassStr, !.ColouredClassStrs) ->
          unexpected($module, $pred, "repeated table_column_class")
      ;
-        set.insert(!.ColouredClassStrs, ColumnClassStr, !:ColouredClassStrs)
+        set.insert(ColumnClassStr, !ColouredClassStrs)
      ),
      ( map.search(!.StyleControlMap, StyleControl, StyleElementMap0) ->
          map.set(StyleElement, Colour, StyleElementMap0, StyleElementMap),
Index: deep_profiler/program_representation_utils.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/program_representation_utils.m,v
retrieving revision 1.34
diff -u -r1.34 program_representation_utils.m
--- deep_profiler/program_representation_utils.m	3 May 2011 04:35:00 -0000	1.34
+++ deep_profiler/program_representation_utils.m	5 May 2011 13:56:45 -0000
@@ -959,7 +959,7 @@
                          ; Inst = ir_other_rep
                          ),
                          % This variable has become more instantiated.
-                        set.insert(Set0, Var, Set)
+                        set.insert(Var, Set0, Set)
                      )
                  ;
                      BeforeInst = ir_ground_rep,
@@ -997,7 +997,7 @@
                      ; Inst = ir_other_rep
                      ),
                      % This variable has become more instantiated.
-                    set.insert(Set0, Var, Set)
+                    set.insert(Var, Set0, Set)
                  )
              )
          ), After ^ im_inst_map, set.init, DeltaVars).
@@ -1012,7 +1012,7 @@
          ; AtomicGoal = method_call_rep(Var, _, VarsL)
          ),
          Vars0 = list_to_set(VarsL),
-        set.insert(Vars0, Var, Vars)
+        set.insert(Var, Vars0, Vars)
      ;
          ( AtomicGoal = partial_construct_rep(Var, _, MaybeVars)
          ; AtomicGoal = partial_deconstruct_rep(Var, _, MaybeVars)
@@ -1020,12 +1020,12 @@
          list.foldl((pred(MaybeVar::in, Set0::in, Set::out) is det :-
                  (
                      MaybeVar = yes(VarI),
-                    set.insert(Set0, VarI, Set)
+                    set.insert(VarI, Set0, Set)
                  ;
                      MaybeVar = no,
                      Set = Set0
                  )), MaybeVars, set.init, Vars0),
-        set.insert(Vars0, Var, Vars)
+        set.insert(Var, Vars0, Vars)
      ;
          ( AtomicGoal = unify_assign_rep(VarA, VarB)
          ; AtomicGoal = cast_rep(VarA, VarB)
Index: deep_profiler/var_use_analysis.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/var_use_analysis.m,v
retrieving revision 1.15
diff -u -r1.15 var_use_analysis.m
--- deep_profiler/var_use_analysis.m	27 Jan 2011 08:03:54 -0000	1.15
+++ deep_profiler/var_use_analysis.m	5 May 2011 13:57:04 -0000
@@ -273,7 +273,7 @@
                      % Don't follow this recursive call as normal, doing so
                      % would make this analysis take too long.  We can compute
                      % the cost of variable use time by the following formula:
-                    set.insert(CallStack0, CalleePDPtr, CallStack),
+                    set.insert(CalleePDPtr, CallStack0, CallStack),
                      proc_dynamic_recursive_var_use_info(ParentCliquePtr,
                          CalleePDPtr, ArgNum, RecursionType, Depth, Cost,
                          CallStack, VarUseOptions, MaybeVarUseInfo0),
Index: extras/moose/grammar.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/extras/moose/grammar.m,v
retrieving revision 1.12
diff -u -r1.12 grammar.m
--- extras/moose/grammar.m	3 May 2011 04:35:00 -0000	1.12
+++ extras/moose/grammar.m	5 May 2011 14:27:34 -0000
@@ -260,11 +260,11 @@
  		error("epsilon start rule")
  	),
  	varset.init(VarSet0),
-	varset.new_vars(VarSet0, Arity, Vars, VarSet1),
+	varset.new_vars(Arity, Vars, VarSet0, VarSet1),
  	list.foldl((pred(V::in, VS0::in, VS::out) is det :-
  		term.var_to_int(V, I),
  		string.format("V%d", [i(I)], N),
-		varset.name_var(VS0, V, N, VS)
+		varset.name_var(V, N, VS0, VS)
  	), Vars, VarSet1, VarSet),
  	term.var_list_to_term_list(Vars, Args),
  	Context = context("foobie", 1),
@@ -463,7 +463,7 @@
  				% it was there in the first place), since
  				% this rule is certainly not nullable.
  			Elem = terminal(Id),
-			set.insert(Set0, Id, Set1),
+			set.insert(Id, Set0, Set1),
  			set.difference(Set1, set.make_singleton_set(epsilon),
  				Set)
  		;
Index: extras/moose/lalr.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/extras/moose/lalr.m,v
retrieving revision 1.8
diff -u -r1.8 lalr.m
--- extras/moose/lalr.m	3 May 2011 04:35:00 -0000	1.8
+++ extras/moose/lalr.m	5 May 2011 14:28:55 -0000
@@ -155,7 +155,7 @@
  :- mode lr0items1(in, in, in, in, out, in, out) is det.

  lr0items1(Pending0, Productions, Reaching, !Gotos, !C) :-
-	( set.remove_least(Pending0, J, Pending1) ->
+	( set.remove_least(J, Pending0, Pending1) ->
  		set.to_sorted_list(J, JList),
  		lr0items_1(JList, J, Productions, Reaching, !Gotos, set.init,
  			NewSet),
@@ -343,8 +343,8 @@
  		( BSym = nonterminal(Bn) ->
  			Bf0 = first(First, Asyms, Ad + 1),
  			( set.member(epsilon, Bf0) ->
-				set.delete(Bf0, epsilon, Bf1),
-				set.insert(Bf1, Asym, Bf)
+				set.delete(epsilon, Bf0, Bf1),
+				set.insert(Asym, Bf1, Bf)
  				%Bf = Bf1 \/ { Asym }
  			;
  				Bf = Bf0
@@ -468,7 +468,7 @@
  	;
  		set.init(As1)
  	),
-	set.insert(As1, A, As),
+	set.insert(A, As1, As),
  	map.set(Ia, As, Y1, Y),
  	map.set(B, Y, X1, X),
  	map.set(I, X, P0, P).
@@ -487,7 +487,7 @@
  	;
  		set.init(As1)
  	),
-	set.insert(As1, Alpha, As),
+	set.insert(Alpha, As1, As),
  	map.set(B, As, X1, X),
  	map.set(I, X, L0, L).

Index: extras/moose/moose.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/extras/moose/moose.m,v
retrieving revision 1.14
diff -u -r1.14 moose.m
--- extras/moose/moose.m	3 May 2011 04:35:00 -0000	1.14
+++ extras/moose/moose.m	5 May 2011 14:32:53 -0000
@@ -549,7 +549,7 @@
      error("terminal_to_term: unexpected epsilon").
  terminal_to_term(Name/Arity, _, Term) :-
      varset.init(V0),
-    varset.new_vars(V0, Arity, Vars, _),
+    varset.new_vars(Arity, Vars, V0, _),
      term.context_init(Ctxt),
      list.map((pred(Var::in, T::out) is det :-
          T = variable(Var, Ctxt)
@@ -630,7 +630,7 @@
      error("nonterminal_to_term: unexpected start").
  nonterminal_to_term(Name/Arity, Term) :-
      varset.init(V0),
-    varset.new_vars(V0, Arity, Vars, _),
+    varset.new_vars(Arity, Vars, V0, _),
      term.context_init(Ctxt),
      list.map((pred(Var::in, T::out) is det :-
          T = variable(Var, Ctxt)
@@ -740,7 +740,7 @@
          true
      ;
          string.format("V%d", [i(N)], VarName),
-        varset.new_named_var(!.Varset, VarName, Var, !:Varset),
+        varset.new_named_var(VarName, Var, !Varset),
          Term = term.variable(Var, context_init),
          list.append([Term], !Terms),
          mkstartargs(N - 1, !Terms, !Varset)
@@ -826,28 +826,28 @@
              !IO),
          Rule = rule(RNt, Head, _, Body, Actions, Varset0, _C),
          term.context_init(Ctxt),
-        varset.new_named_var(Varset0, "M_St0", St0v, Varset1),
+        varset.new_named_var("M_St0", St0v, Varset0, Varset1),
          St0 = variable(St0v, Ctxt),
-        varset.new_named_var(Varset1, "M_St1", St1v, Varset2),
+        varset.new_named_var("M_St1", St1v, Varset1, Varset2),
          St1 = variable(St1v, Ctxt),
-        varset.new_named_var(Varset2, "M_Sy0", Sy0v, Varset3),
+        varset.new_named_var("M_Sy0", Sy0v, Varset2, Varset3),
          Sy0 = variable(Sy0v, Ctxt),
-        varset.new_named_var(Varset3, "M_Sy1", Sy1v, Varset4),
+        varset.new_named_var("M_Sy1", Sy1v, Varset3, Varset4),
          Sy1 = variable(Sy1v, Ctxt),
-        varset.new_named_var(Varset4, "M_RedRes", Resv, Varset5),
+        varset.new_named_var("M_RedRes", Resv, Varset4, Varset5),
          Res = variable(Resv, Ctxt),
          ResS = functor(atom("n"), [variable(Resv, Ctxt)], Ctxt),
-        varset.new_named_var(Varset5, "M_D", Dv, Varset6),
+        varset.new_named_var("M_D", Dv, Varset5, Varset6),
          _D = variable(Dv, Ctxt),
-        varset.new_named_var(Varset6, "M_S", Sv, Varset7),
+        varset.new_named_var("M_S", Sv, Varset6, Varset7),
          _S = variable(Sv, Ctxt),
-        varset.new_named_var(Varset7, "M_St", Stv, Varset8),
+        varset.new_named_var("M_St", Stv, Varset7, Varset8),
          St = variable(Stv, Ctxt),
-        varset.new_named_var(Varset8, "M_Sy", Syv, Varset9),
+        varset.new_named_var("M_Sy", Syv, Varset8, Varset9),
          Sy = variable(Syv, Ctxt),
-        varset.new_named_var(Varset9, "M_Ts0", Ts0v, Varset10),
+        varset.new_named_var("M_Ts0", Ts0v, Varset9, Varset10),
          Ts0 = variable(Ts0v, Ctxt),
-        varset.new_named_var(Varset10, "M_Ts", Tsv, Varset11),
+        varset.new_named_var("M_Ts", Tsv, Varset10, Varset11),
          Ts = variable(Tsv, Ctxt),
          string.format("reduction 0x%x failed!", [i(Rn)], Err),
          mkstacks(Body, St1, Sts, Sy1, Sys, Varset11, Varset12),
@@ -923,7 +923,7 @@

  mkstacks([], !St, !Sy, !VS).
  mkstacks([E0 | Es], !St, !Sy, !VS) :-
-    varset.new_var(!.VS, U, !:VS),
+    varset.new_var(U, !VS),
      term.context_init(Ctxt),
      (
          E0 = terminal(ET),
Index: library/eqvclass.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/library/eqvclass.m,v
retrieving revision 1.27
diff -u -r1.27 eqvclass.m
--- library/eqvclass.m	3 May 2011 05:12:04 -0000	1.27
+++ library/eqvclass.m	5 May 2011 10:23:21 -0000
@@ -253,7 +253,7 @@
          ;
              PartitionMap0 = EqvClass0 ^ partitions,
              map.lookup(PartitionMap0, IdA, PartitionA),
-            set.insert(PartitionA, ElementB, Partition),
+            set.insert(ElementB, PartitionA, Partition),
              map.det_update(IdA, Partition, PartitionMap0, PartitionMap),
              map.det_insert(ElementB, IdA, ElementMap0, ElementMap),
              NextId0 = EqvClass0 ^ next_id,
@@ -263,7 +263,7 @@
          ( map.search(ElementMap0, ElementB, IdB) ->
              PartitionMap0 = EqvClass0 ^ partitions,
              map.lookup(PartitionMap0, IdB, PartitionB),
-            set.insert(PartitionB, ElementA, Partition),
+            set.insert(ElementA, PartitionB, Partition),
              map.det_update(IdB, Partition, PartitionMap0, PartitionMap),
              map.det_insert(ElementA, IdB, ElementMap0, ElementMap),
              NextId0 = EqvClass0 ^ next_id,
@@ -298,7 +298,7 @@
          ;
              PartitionMap0 = EqvClass0 ^ partitions,
              map.lookup(PartitionMap0, IdA, PartitionA),
-            set.insert(PartitionA, ElementB, Partition),
+            set.insert(ElementB, PartitionA, Partition),
              map.det_update(IdA, Partition, PartitionMap0, PartitionMap),
              map.det_insert(ElementB, IdA, ElementMap0, ElementMap),
              NextId0 = EqvClass0 ^ next_id,
@@ -308,7 +308,7 @@
          ( map.search(ElementMap0, ElementB, IdB) ->
              PartitionMap0 = EqvClass0 ^ partitions,
              map.lookup(PartitionMap0, IdB, PartitionB),
-            set.insert(PartitionB, ElementA, Partition),
+            set.insert(ElementA, PartitionB, Partition),
              map.det_update(IdB, Partition, PartitionMap0, PartitionMap),
              map.det_insert(ElementA, IdB, ElementMap0, ElementMap),
              NextId0 = EqvClass0 ^ next_id,
@@ -536,11 +536,11 @@
              true
          ;
              map.lookup(!.Partitions, MainId, MainSet0),
-            set.delete(MainSet0, Item, MainSet),
+            set.delete(Item, MainSet0, MainSet),
              map.det_update(MainId, MainSet, !Partitions),

              map.lookup(!.Partitions, Id, Set0),
-            set.insert(Set0, Item, Set),
+            set.insert(Item, Set0, Set),
              map.det_update(Id, Set, !Partitions),

              map.det_update(Item, Id, !Keys)
@@ -550,7 +550,7 @@
          map.det_insert(Value, NewId, !Map),

          map.lookup(!.Partitions, MainId, MainSet0),
-        set.delete(MainSet0, Item, MainSet),
+        set.delete(Item, MainSet0, MainSet),
          map.det_update(MainId, MainSet, !Partitions),

          Set = set.make_singleton_set(Item),
Index: library/set.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/library/set.m,v
retrieving revision 1.90
diff -u -r1.90 set.m
--- library/set.m	16 Feb 2011 02:11:50 -0000	1.90
+++ library/set.m	5 May 2011 14:09:58 -0000
@@ -103,70 +103,54 @@
      %
  :- pred set.contains(set(T)::in, T::in) is semidet.

-    % `set.insert(Set0, X, Set)' is true iff `Set' is the union of
+    % `set.insert(X, Set0, Set)' is true iff `Set' is the union of
      % `Set0' and the set containing only `X'.
      %
-:- pred set.insert(set(T)::in, T::in, set(T)::out) is det.
-
-    % XXX rwab1: I think we should reverse the args. here for
-    % higher order programming.
-    %
  :- func set.insert(set(T), T) = set(T).
+:- pred set.insert(T::in, set(T)::in, set(T)::out) is det.

-    % `set.insert_list(Set0, Xs, Set)' is true iff `Set' is the union of
+    % `set.insert_list(Xs, Set0, Set)' is true iff `Set' is the union of
      % `Set0' and the set containing only the members of `Xs'.
      %
-:- pred set.insert_list(set(T)::in, list(T)::in, set(T)::out) is det.
-
-    % XXX rwab1: I think we should reverse the args. here for
-    % higher order programming.
-    %
  :- func set.insert_list(set(T), list(T)) = set(T).
+:- pred set.insert_list(list(T)::in, set(T)::in, set(T)::out) is det.

-    % `set.delete(Set0, X, Set)' is true iff `Set' is the relative
+    % `set.delete(X, Set0, Set)' is true iff `Set' is the relative
      % complement of `Set0' and the set containing only `X', i.e.
      % if `Set' is the set which contains all the elements of `Set0'
      % except `X'.
      %
-:- pred set.delete(set(T)::in, T::in, set(T)::out) is det.
-
-    % XXX rwab1: I think we should reverse the args. here for
-    % higher order programming.
-    %
  :- func set.delete(set(T), T) = set(T).
+:- pred set.delete(T::in, set(T)::in, set(T)::out) is det.

      % `set.delete_list(Set0, Xs, Set)' is true iff `Set' is the relative
      % complement of `Set0' and the set containing only the members of
      % `Xs'.
      %
-:- pred set.delete_list(set(T)::in, list(T)::in, set(T)::out) is det.
-
-    % XXX rwab1: I think we should reverse the args. here for
-    % higher order programming.
-    %
  :- func set.delete_list(set(T), list(T)) = set(T).
+:- pred set.delete_list(list(T)::in, set(T)::in, set(T)::out) is det.

-    % `set.remove(Set0, X, Set)' is true iff `Set0' contains `X',
+    % `set.remove(X, Set0, Set)' is true iff `Set0' contains `X',
      % and `Set' is the relative complement of `Set0' and the set
      % containing only `X', i.e.  if `Set' is the set which contains
      % all the elements of `Set0' except `X'.
      %
-:- pred set.remove(set(T)::in, T::in, set(T)::out) is semidet.
+:- pred set.remove(T::in, set(T)::in, set(T)::out) is semidet.

-    % `set.remove_list(Set0, Xs, Set)' is true iff `Xs' does not
+    % `set.remove_list(Xs, Set0, Set)' is true iff `Xs' does not
      % contain any duplicates, `Set0' contains every member of `Xs',
      % and `Set' is the relative complement of `Set0' and the set
      % containing only the members of `Xs'.
      %
-:- pred set.remove_list(set(T)::in, list(T)::in, set(T)::out) is semidet.
+:- pred set.remove_list(list(T)::in, set(T)::in, set(T)::out) is semidet.

-    % `set.remove_least(Set0, Elem, Set)' is true iff
+    % `set.remove_least(Elem, Set0, Set)' is true iff
      % `Set0' is not empty, `Elem' is the smallest element in `Set0'
      % (with elements ordered using the standard ordering given
      % by compare/3), and `Set' is the set containing all the
      % elements of `Set0' except `Elem'.
      %
-:- pred set.remove_least(set(T)::in, T::out, set(T)::out) is semidet.
+:- pred set.remove_least(T::out, set(T)::in, set(T)::out) is semidet.

      % `set.union(SetA, SetB, Set)' is true iff `Set' is the union of
      % `SetA' and `SetB'.  If the sets are known to be of different
@@ -177,8 +161,8 @@
      % will make it less likely that you will encounter problems if
      % the implementation is changed.)
      %
-:- pred set.union(set(T)::in, set(T)::in, set(T)::out) is det.
  :- func set.union(set(T), set(T)) = set(T).
+:- pred set.union(set(T)::in, set(T)::in, set(T)::out) is det.

      % `set.union_list(A, B)' is true iff `B' is the union of
      % all the sets in `A'.
@@ -188,8 +172,8 @@
      % `set.power_union(A, B)' is true iff `B' is the union of
      % all the sets in `A'.
      %
-:- pred set.power_union(set(set(T))::in, set(T)::out) is det.
  :- func set.power_union(set(set(T))) = set(T).
+:- pred set.power_union(set(set(T))::in, set(T)::out) is det.

      % `set.intersect(SetA, SetB, Set)' is true iff `Set' is the
      % intersection of `SetA' and `SetB'. If the two sets are
@@ -201,14 +185,14 @@
      % will make it less likely that you will encounter problems if
      % the implementation is changed.)
      %
-:- pred set.intersect(set(T)::in, set(T)::in, set(T)::out) is det.
  :- func set.intersect(set(T), set(T)) = set(T).
+:- pred set.intersect(set(T)::in, set(T)::in, set(T)::out) is det.

      % `set.power_intersect(A, B)' is true iff `B' is the intersection of
      % all the sets in `A'.
      %
-:- pred set.power_intersect(set(set(T))::in, set(T)::out) is det.
  :- func set.power_intersect(set(set(T))) = set(T).
+:- pred set.power_intersect(set(set(T))::in, set(T)::out) is det.

      % `set.intersect_list(A, B)' is true iff `B' is the intersection of
      % all the sets in `A'.
@@ -219,23 +203,27 @@
      % set containing all the elements of `SetA' except those that
      % occur in `SetB'.
      %
-:- pred set.difference(set(T)::in, set(T)::in, set(T)::out) is det.
  :- func set.difference(set(T), set(T)) = set(T).
+:- pred set.difference(set(T)::in, set(T)::in, set(T)::out) is det.

      % `set.count(Set, Count)' is true iff `Set' has `Count' elements.
      % i.e. `Count' is the cardinality (size) of the set.
      %
-:- pred set.count(set(T)::in, int::out) is det.
  :- func set.count(set(T)) = int.
+:- pred set.count(set(T)::in, int::out) is det.

      % Support for higher order set processing.

      % map(F, S) =
      %   list_to_set(list.map(F, to_sorted_list(S))).
      %
-:- pred set.map(pred(T1, T2), set(T1), set(T2)).
-:- mode set.map(in(pred(in, out) is det), in, out) is det.
  :- func set.map(func(T1) = T2, set(T1)) = set(T2).
+:- pred set.map(pred(T1, T2), set(T1), set(T2)).
+:- mode set.map(pred(in, out) is det, in, out) is det.
+:- mode set.map(pred(in, out) is cc_multi, in, out) is cc_multi.
+:- mode set.map(pred(in, out) is semidet, in, out) is semidet.
+:- mode set.map(pred(in, out) is multi, in, out) is multi.
+:- mode set.map(pred(in, out) is nondet, in, out) is nondet.

      % set.map_fold(P, S0, S, A0, A) :-
      %   L0 = set.to_sorted_list(S0),
@@ -244,6 +232,15 @@
      %
  :- pred set.map_fold(pred(T1, T2, T3, T3), set(T1), set(T2), T3, T3).
  :- mode set.map_fold(pred(in, out, in, out) is det, in, out, in, out) is det.
+:- mode set.map_fold(pred(in, out, mdi, muo) is det, in, out, mdi, muo) is det.
+:- mode set.map_fold(pred(in, out, di, uo) is det, in, out, di, uo) is det.
+:- mode set.map_fold(pred(in, out, in, out) is semidet, in, out,
+    in, out) is semidet.
+:- mode set.map_fold(pred(in, out, mdi, muo) is semidet, in, out,
+    mdi, muo) is semidet.
+:- mode set.map_fold(pred(in, out, di, uo) is semidet, in, out,
+    di, uo) is semidet.
+

      % set.filter(P, S) =
      %   sorted_list_to_set(list.filter(P, to_sorted_list(S))).
@@ -384,7 +381,7 @@
  :- import_module set_ordlist.
  :- import_module term.  % for var/1.

-:- type set(T) ==   set_ordlist(T).
+:- type set(T) == set_ordlist(T).

  :- pragma type_spec(set.list_to_set/2, T = var(_)).
  :- pragma type_spec(set.list_to_set/1, T = var(_)).
@@ -412,6 +409,24 @@

  :- implementation.

+set.init = S :-
+    set.init(S).
+
+set.init(Set) :-
+    set_ordlist.init(Set).
+
+set.make_singleton_set(T) = S :-
+    set.singleton_set(S, T).
+
+set.singleton_set(Set, X) :-
+    set_ordlist.singleton_set(Set, X).
+
+set.list_to_set(Xs) = S :-
+    set.list_to_set(Xs, S).
+
+set.sorted_list_to_set(Xs) = S :-
+    set.sorted_list_to_set(Xs, S).
+
  set.list_to_set(List, Set) :-
      set_ordlist.list_to_set(List, Set).

@@ -424,20 +439,23 @@

  set.from_sorted_list(List) = set_ordlist.from_sorted_list(List).

+set.to_sorted_list(S) = Xs :-
+    set.to_sorted_list(S, Xs).
+
  set.to_sorted_list(Set, List) :-
      set_ordlist.to_sorted_list(Set, List).

-set.insert_list(Set0, List, Set) :-
-    set_ordlist.insert_list(Set0, List, Set).
+set.insert_list(S1, Xs) = S2 :-
+    set.insert_list(Xs, S1, S2).

-set.insert(Set0, X, Set) :-
-    set_ordlist.insert(Set0, X, Set).
+set.insert_list(List, Set0, Set) :-
+    set_ordlist.insert_list(Set0, List, Set).

-set.init(Set) :-
-    set_ordlist.init(Set).
+set.insert(S1, T) = S2 :-
+    set.insert(T, S1, S2).

-set.singleton_set(Set, X) :-
-    set_ordlist.singleton_set(Set, X).
+set.insert(X, !Set) :-
+    set_ordlist.insert(!.Set, X, !:Set).

  set.equal(SetA, SetB) :-
      set_ordlist.equal(SetA, SetB).
@@ -467,32 +485,53 @@
  set.contains(Set, X) :-
      set_ordlist.contains(Set, X).

-set.delete_list(Set0, List, Set) :-
+set.delete_list(S1, Xs) = S2 :-
+    set.delete_list(Xs, S1, S2).
+
+set.delete_list(List, Set0, Set) :-
      set_ordlist.delete_list(Set0, List, Set).

-set.delete(Set0, X, Set) :-
+set.delete(S1, T) = S2 :-
+    set.delete(T, S1, S2).
+
+set.delete(X, Set0, Set) :-
      set_ordlist.delete(Set0, X, Set).

-set.remove_list(Set0, List, Set) :-
+set.remove_list(List, Set0, Set) :-
      set_ordlist.remove_list(Set0, List, Set).

-set.remove(Set0, X, Set) :-
+set.remove(X, Set0, Set) :-
      set_ordlist.remove(Set0, X, Set).

-set.remove_least(Set0, X, Set) :-
+set.remove_least(X, Set0, Set) :-
      set_ordlist.remove_least(Set0, X, Set).

+set.union(S1, S2) = S3 :-
+    set.union(S1, S2, S3).
+
  set.union(SetA, SetB, Set) :-
      set_ordlist.union(SetA, SetB, Set).

  set.union_list(Sets) = set_ordlist.union_list(Sets).

+set.power_union(SS) = S :-
+    set.power_union(SS, S).
+
  set.power_union(Sets, Set) :-
      set_ordlist.power_union(Sets, Set).

+set.intersect(S1, S2) = S3 :-
+    set.intersect(S1, S2, S3).
+
  set.intersect(SetA, SetB, Set) :-
      set_ordlist.intersect(SetA, SetB, Set).

+set.power_intersect(SS) = S :-
+    set.power_intersect(SS, S).
+
+set.difference(S1, S2) = S3 :-
+    set.difference(S1, S2, S3).
+
  set.power_intersect(Sets, Set) :-
      set_ordlist.power_intersect(Sets, Set).

@@ -501,59 +540,12 @@
  set.difference(SetA, SetB, Set) :-
      set_ordlist.difference(SetA, SetB, Set).

-set.count(Set, Count) :-
-    set_ordlist.count(Set, Count).
-
-%--------------------------------------------------------------------------%
-%--------------------------------------------------------------------------%
-% Ralph Becket <rwab1 at cam.sri.com> 24/04/99
-%   Function forms added.
-
-set.list_to_set(Xs) = S :-
-    set.list_to_set(Xs, S).
-
-set.sorted_list_to_set(Xs) = S :-
-    set.sorted_list_to_set(Xs, S).
-
-set.to_sorted_list(S) = Xs :-
-    set.to_sorted_list(S, Xs).
-
-set.init = S :-
-    set.init(S).
-
-set.make_singleton_set(T) = S :-
-    set.singleton_set(S, T).
-
-set.insert(S1, T) = S2 :-
-    set.insert(S1, T, S2).
-
-set.insert_list(S1, Xs) = S2 :-
-    set.insert_list(S1, Xs, S2).
-
-set.delete(S1, T) = S2 :-
-    set.delete(S1, T, S2).
-
-set.delete_list(S1, Xs) = S2 :-
-    set.delete_list(S1, Xs, S2).
-
-set.union(S1, S2) = S3 :-
-    set.union(S1, S2, S3).
-
-set.power_union(SS) = S :-
-    set.power_union(SS, S).
-
-set.intersect(S1, S2) = S3 :-
-    set.intersect(S1, S2, S3).
-
-set.power_intersect(SS) = S :-
-    set.power_intersect(SS, S).
-
-set.difference(S1, S2) = S3 :-
-    set.difference(S1, S2, S3).
-
  set.count(S) = N :-
      set.count(S, N).

+set.count(Set, Count) :-
+    set_ordlist.count(Set, Count).
+
  set.map(P, S1, S2) :-
      set.to_sorted_list(S1, L1),
      list.map(P, L1, L2),
@@ -604,3 +596,7 @@

  set.divide_by_set(DivideBySet, Set, TruePart, FalsePart) :-
      set_ordlist.divide_by_set(DivideBySet, Set, TruePart, FalsePart).
+
+%--------------------------------------------------------------------------%
+:- end_module set.
+%--------------------------------------------------------------------------%
Index: library/svset.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/library/svset.m,v
retrieving revision 1.8
diff -u -r1.8 svset.m
--- library/svset.m	19 Apr 2006 05:17:58 -0000	1.8
+++ library/svset.m	5 May 2011 10:20:16 -0000
@@ -89,23 +89,23 @@

  :- implementation.

-svset.insert(X, Set0, Set) :-
-    set.insert(Set0, X, Set).
+svset.insert(X, !Set) :-
+    set.insert(X, !Set).

-svset.insert_list(X, Set0, Set) :-
-    set.insert_list(Set0, X, Set).
+svset.insert_list(X, !Set) :-
+    set.insert_list(X, !Set).

-svset.delete(X, Set0, Set) :-
-    set.delete(Set0, X, Set).
+svset.delete(X, !Set) :-
+    set.delete(X, !Set).

-svset.delete_list(X, Set0, Set) :-
-    set.delete_list(Set0, X, Set).
+svset.delete_list(X, !Set) :-
+    set.delete_list(X, !Set).

-svset.remove(X, Set0, Set) :-
-    set.remove(Set0, X, Set).
+svset.remove(X, !Set) :-
+    set.remove(X, !Set).

-svset.remove_list(X, Set0, Set) :-
-    set.remove_list(Set0, X, Set).
+svset.remove_list(X, !Set) :-
+    set.remove_list(X, !Set).

-svset.remove_least(X, Set0, Set) :-
-    set.remove_least(Set0, X, Set).
+svset.remove_least(X, !Set) :-
+    set.remove_least(X, !Set).
Index: library/tree234.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/library/tree234.m,v
retrieving revision 1.71
diff -u -r1.71 tree234.m
--- library/tree234.m	5 May 2011 04:35:34 -0000	1.71
+++ library/tree234.m	5 May 2011 10:06:23 -0000
@@ -3460,7 +3460,7 @@
      set(int)::in, set(int)::out) is det.

  depth_levels(empty, Depth, !Depths) :-
-    set.insert(!.Depths, Depth, !:Depths).
+    set.insert(Depth, !Depths).
  depth_levels(two(_, _, T1, T2), Depth, !Depths) :-
      NextDepth = Depth + 1,
      depth_levels(T1, NextDepth, !Depths),
Index: library/varset.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/library/varset.m,v
retrieving revision 1.88
diff -u -r1.88 varset.m
--- library/varset.m	5 May 2011 03:58:59 -0000	1.88
+++ library/varset.m	5 May 2011 10:19:09 -0000
@@ -613,10 +613,10 @@
      map(var(T), string)::out) is det.

  varset.ensure_unique_names_2([], _, _, _, !VarNames).
-varset.ensure_unique_names_2([Var | Vars], Suffix, UsedNames0, OldVarNames,
+varset.ensure_unique_names_2([Var | Vars], Suffix, !.UsedNames, OldVarNames,
          !VarNames) :-
      ( map.search(OldVarNames, Var, OldName) ->
-        ( set.member(OldName, UsedNames0) ->
+        ( set.member(OldName, !.UsedNames) ->
              term.var_to_int(Var, VarNum),
              string.int_to_string(VarNum, NumStr),
              string.append("_", NumStr, NumSuffix),
@@ -629,10 +629,10 @@
          string.int_to_string(VarNum, NumStr),
          string.append("Var_", NumStr, TrialName)
      ),
-    append_suffix_until_unique(TrialName, Suffix, UsedNames0, FinalName),
-    set.insert(UsedNames0, FinalName, UsedNames1),
+    append_suffix_until_unique(TrialName, Suffix, !.UsedNames, FinalName),
+    set.insert(FinalName, !UsedNames),
      map.det_insert(Var, FinalName, !VarNames),
-    varset.ensure_unique_names_2(Vars, Suffix, UsedNames1, OldVarNames,
+    varset.ensure_unique_names_2(Vars, Suffix, !.UsedNames, OldVarNames,
          !VarNames).

  :- pred append_suffix_until_unique(string::in, string::in, set(string)::in,
Index: mdbcomp/trace_counts.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/mdbcomp/trace_counts.m,v
retrieving revision 1.28
diff -u -r1.28 trace_counts.m
--- mdbcomp/trace_counts.m	3 May 2011 04:35:01 -0000	1.28
+++ mdbcomp/trace_counts.m	5 May 2011 10:25:42 -0000
@@ -992,5 +992,5 @@

  insert_into_list_as_set(List0, Item) = List :-
      set.list_to_set(List0, Set0),
-    set.insert(Set0, Item, Set),
+    set.insert(Item, Set0, Set),
      set.to_sorted_list(Set, List).
Index: tests/hard_coded/bitset_tester.m
===================================================================
RCS file: /home/mercury/mercury1/repository/tests/hard_coded/bitset_tester.m,v
retrieving revision 1.5
diff -u -r1.5 bitset_tester.m
--- tests/hard_coded/bitset_tester.m	15 Dec 2006 00:05:31 -0000	1.5
+++ tests/hard_coded/bitset_tester.m	5 May 2011 16:28:22 -0000
@@ -136,13 +136,13 @@

  remove(SetA0 - SetB0, Elem) = Result :-
  	( remove(SetA0, Elem, SetA1) ->
-		( remove(SetB0, Elem, SetB1) ->
+		( remove(Elem, SetB0, SetB1) ->
  			SetA = SetA1,
  			SetB = SetB1
  		;
  			error("remove succeeded unexpectedly")
  		)
-	; set__remove(SetB0, Elem, _) ->
+	; set__remove(Elem, SetB0, _) ->
  		error("remove failed unexpectedly")
  	;
  		fail
@@ -151,13 +151,13 @@

  remove_list(SetA0 - SetB0, List) = Result :-
  	( remove_list(SetA0, List, SetA1) ->
-		( set__remove_list(SetB0, List, SetB1) ->
+		( set__remove_list(List, SetB0, SetB1) ->
  			SetA = SetA1,
  			SetB = SetB1
  		;
  			error("remove succeeded unexpectedly")
  		)
-	; set__remove_list(SetB0, List, _) ->
+	; set__remove_list(List, SetB0, _) ->
  		error("remove failed unexpectedly")
  	;
  		fail
@@ -264,7 +264,7 @@

  remove_least(SetA0 - SetB0, Least, SetA - SetB) :-
  	( remove_least(SetA0, LeastA, SetA1) ->
-		( remove_least(SetB0, LeastB, SetB1) ->
+		( remove_least(LeastB, SetB0, SetB1) ->
  			( LeastA = LeastB ->
  				SetA = SetA1,
  				SetB = SetB1,
@@ -275,7 +275,7 @@
  		;
  			error("remove_least: should be no least value")
  		)
-	; remove_least(SetB0, _, _) ->
+	; remove_least(_, SetB0, _) ->
  		error("remove_least: failed")
  	;
  		fail

--------------------------------------------------------------------------
mercury-reviews mailing list
Post messages to:       mercury-reviews at csse.unimelb.edu.au
Administrative Queries: owner-mercury-reviews at csse.unimelb.edu.au
Subscriptions:          mercury-reviews-request at csse.unimelb.edu.au
--------------------------------------------------------------------------



More information about the reviews mailing list