[m-rev.] for review: Add take_while and drop_while to the list module

Paul Bone paul at bone.id.au
Thu Apr 21 17:09:07 AEST 2016


On Thu, Apr 21, 2016 at 12:37:12PM +1000, Mark Brown wrote:
> On Thu, Apr 21, 2016 at 12:02 PM, Paul Bone <paul at bone.id.au> wrote:
> > On Thu, Apr 21, 2016 at 11:55:58AM +1000, Mark Brown wrote:
> >> Hi Paul,
> >>
> >> On Thu, Apr 21, 2016 at 11:11 AM, Paul Bone <paul at bone.id.au> wrote:
> >> > For review by anyone
> >> >
> >> > ---
> >> >
> >> > Add take_while and drop_while to the list module
> >>
> >> Are you aware there is already a takewhile predicate in the list module?
> >>
> >
> > No I wasn't, it looks like it behaves differently anyway.
> 
> All the more reason to be aware of it ;-)
> 
> >
> > I noticed that in our YesLogic code we have some utility code that can be
> > put into the Mercury standard library, including a dropwhile predicate.  So
> > I named it drop_while and submitted it and an similar take_while predicate.
> >
> > I don't really mind what happens, does anyone else have any strong ideas
> > about these kinds of predicates?
> 
> The new variants would be better near the existing takewhile, so users
> get a better idea of their options. (I know it's also similar to
> take_upto, but it takes a higher-order argument so is probably better
> grouped with those predicates.)

Here's the updated diff.  I've fixed the doc comment for drop_while, renamed
take_while/4 to split_while/4, and moved it and the deprecated takewhile/4
so that they're after the other split predicates but before the take
predicates.  I think this a better name than take_while, and a
re-arrangement to put predicates near to other relevant ones.


>From 761f0fbc92794c92eb3050a1722624d3a0e78a20 Mon Sep 17 00:00:00 2001
From: Paul Bone <paul at bone.id.au>
Date: Thu, 21 Apr 2016 11:00:49 +1000
Subject: [PATCH] Add take_while and drop_while to the list module

Add new predicates and functions take_while and drop_while to the list
module.

Deprecate takewhile/4, replacing it with split_while/4.

library/list.m:
    As above.

NEWS:
    Announce this change.

browser/parse.m:
compiler/compute_grade.m:
compiler/deforest.m:
compiler/mercury_compile_main.m:
compiler/ml_optimize.m:
compiler/mode_robdd.equiv_vars.m:
compiler/options_file.m:
compiler/structure_reuse.direct.choose_reuse.m:
compiler/structure_reuse.domain.m:
compiler/structure_sharing.domain.m:
compiler/term_constr_data.m:
compiler/write_deps_file.m:
compiler/xml_documentation.m:
deep_profiler/read_profile.m:
deep_profiler/top_procs.m:
library/list.m:
    Conform to above changes.
---
 NEWS                                           |  8 +++
 browser/parse.m                                |  4 +-
 compiler/compute_grade.m                       |  2 +-
 compiler/deforest.m                            |  2 +-
 compiler/mercury_compile_main.m                |  4 +-
 compiler/ml_optimize.m                         |  4 +-
 compiler/mode_robdd.equiv_vars.m               |  4 +-
 compiler/options_file.m                        | 10 +--
 compiler/structure_reuse.direct.choose_reuse.m |  2 +-
 compiler/structure_reuse.domain.m              |  4 +-
 compiler/structure_sharing.domain.m            |  8 +--
 compiler/term_constr_data.m                    |  2 +-
 compiler/write_deps_file.m                     |  2 +-
 compiler/xml_documentation.m                   |  4 +-
 deep_profiler/read_profile.m                   |  2 +-
 deep_profiler/top_procs.m                      |  4 +-
 library/list.m                                 | 91 ++++++++++++++++++++------
 17 files changed, 108 insertions(+), 49 deletions(-)

diff --git a/NEWS b/NEWS
index c269b21..313e4a9 100644
--- a/NEWS
+++ b/NEWS
@@ -280,6 +280,14 @@ Changes to the Mercury standard library:
 
    - reverse_prepend/2
    - reverse_prepend/3
+   - take_while/3
+   - take_while/2
+   - drop_while/3
+   - drop_while/2
+   - split_while/4
+
+* The dropwhile/4 predicate has been deprecated in the list module,
+  split_while/4 can be used instead.
 
 * The following predicate and function in the builtin module have been
   deprecated and will be removed in a future release:
diff --git a/browser/parse.m b/browser/parse.m
index 495d1de..9c1ef9c 100644
--- a/browser/parse.m
+++ b/browser/parse.m
@@ -315,7 +315,7 @@ lexer_arg([Head | Tail], Toks) :-
 :- pred lexer_num(int::in, list(char)::in, list(token)::out) is det.
 
 lexer_num(N, Cs, Toks) :-
-    list.takewhile(char.is_digit, Cs, Digits, Rest),
+    list.split_while(char.is_digit, Cs, Digits, Rest),
     digits_to_int_acc(N, Digits, Num),
     Toks = [token_num(Num) | Toks2],
     lexer_word_chars(Rest, Toks2).
@@ -331,7 +331,7 @@ digits_to_int_acc(Acc, [C | Cs], Num) :-
 :- pred lexer_name(char::in, list(char)::in, list(token)::out) is det.
 
 lexer_name(C, Cs, Toks) :-
-    list.takewhile(char.is_alnum_or_underscore, Cs, Letters, Rest),
+    list.split_while(char.is_alnum_or_underscore, Cs, Letters, Rest),
     string.from_char_list([C | Letters], Name),
     lexer_word_chars(Rest, Toks2),
     Toks = [token_name(Name) | Toks2].
diff --git a/compiler/compute_grade.m b/compiler/compute_grade.m
index 63ea094..41aa3ad 100644
--- a/compiler/compute_grade.m
+++ b/compiler/compute_grade.m
@@ -809,7 +809,7 @@ split_grade_string(GradeStr, Components) :-
 split_grade_string_2([], []).
 split_grade_string_2(Chars, Components) :-
     Chars = [_ | _],
-    list.takewhile(char_is_not('.'), Chars, ThisChars, RestChars0),
+    list.split_while(char_is_not('.'), Chars, ThisChars, RestChars0),
     string.from_char_list(ThisChars, ThisComponent),
     Components = [ThisComponent | RestComponents],
     (
diff --git a/compiler/deforest.m b/compiler/deforest.m
index cc0541a..b27a9dc 100644
--- a/compiler/deforest.m
+++ b/compiler/deforest.m
@@ -503,7 +503,7 @@ propagate_conj_constraints([Goal0 | Goals0], NonLocals, RevGoals0, Goals,
             _),
         module_info_pred_info(ModuleInfo, PredId, PredInfo),
         not pred_info_is_imported(PredInfo),
-        list.takewhile((pred(CnstrGoal::in) is semidet :-
+        list.split_while((pred(CnstrGoal::in) is semidet :-
             CnstrGoal = hlds_goal(_, CnstrGoalInfo),
             goal_info_has_feature(CnstrGoalInfo, feature_constraint)
         ), Goals0, Constraints, Goals1),
diff --git a/compiler/mercury_compile_main.m b/compiler/mercury_compile_main.m
index 4735b7d..4bd19bc 100644
--- a/compiler/mercury_compile_main.m
+++ b/compiler/mercury_compile_main.m
@@ -1863,11 +1863,11 @@ read_dependency_file_get_modules(TransOptDeps, !IO) :-
         Result = ok(CharList0),
         % Remove any whitespace from the beginning of the line,
         % then take all characters until another whitespace occurs.
-        list.takewhile(char.is_whitespace, CharList0, _, CharList1),
+        list.drop_while(char.is_whitespace, CharList0, CharList1),
         NotIsWhitespace = (pred(Char::in) is semidet :-
             not char.is_whitespace(Char)
         ),
-        list.takewhile(NotIsWhitespace, CharList1, CharList, _),
+        list.take_while(NotIsWhitespace, CharList1, CharList),
         string.from_char_list(CharList, FileName0),
         string.remove_suffix(FileName0, ".trans_opt", FileName)
     then
diff --git a/compiler/ml_optimize.m b/compiler/ml_optimize.m
index 3a1a2a6..8e72c2e 100644
--- a/compiler/ml_optimize.m
+++ b/compiler/ml_optimize.m
@@ -878,8 +878,8 @@ convert_assignments_into_initializers(OptInfo, !Defns, !Statements) :-
         % check that the initializers (if any) of the variables that follow
         % this one don't refer to this variable.
         Qualifier = OptInfo ^ oi_module_name,
-        list.takewhile(isnt(var_defn(VarName)), !.Defns,
-            _PrecedingDefns, [_VarDefn | FollowingDefns]),
+        list.drop_while(isnt(var_defn(VarName)), !.Defns,
+            [_VarDefn | FollowingDefns]),
         Filter = (pred(OtherDefn::in) is semidet :-
             OtherDefn = mlds_defn(entity_data(OtherVarName),
                 _, _, mlds_data(_Type, OtherInitializer, _GC)),
diff --git a/compiler/mode_robdd.equiv_vars.m b/compiler/mode_robdd.equiv_vars.m
index e7e7f75..5fb08cc 100644
--- a/compiler/mode_robdd.equiv_vars.m
+++ b/compiler/mode_robdd.equiv_vars.m
@@ -302,9 +302,9 @@ delete(E0, V) = E :-
 
 restrict_threshold(Th, E) = equiv_vars(normalise_leader_map(LM)) :-
 	LL0 = map.to_assoc_list(E ^ leader_map),
-	list.takewhile((pred((V - _)::in) is semidet :-
+	list.take_while((pred((V - _)::in) is semidet :-
 		\+ compare(>, V, Th)
-		), LL0, LL, _),
+		), LL0, LL),
 	LM = map.from_assoc_list(LL).
 
 % XXX not terribly efficient.
diff --git a/compiler/options_file.m b/compiler/options_file.m
index b96b729..9221495 100644
--- a/compiler/options_file.m
+++ b/compiler/options_file.m
@@ -609,11 +609,11 @@ parse_options_line(Line0, OptionsFileLine) :-
         ),
         list.append(string.to_char_list("include"), Line3, Line2)
     then
-        list.takewhile(char.is_whitespace, Line3, _, Line4),
+        list.drop_while(char.is_whitespace, Line3, Line4),
         OptionsFileLine = include_options_files(ErrorIfNotExist, Line4)
     else
         parse_variable(VarName, Line0, Line1),
-        list.takewhile(char.is_whitespace, Line1, _, Line2),
+        list.drop_while(char.is_whitespace, Line1, Line2),
         ( if Line2 = [('=') | Line3] then
             Add = no,
             Line4 = Line3
@@ -627,7 +627,7 @@ parse_options_line(Line0, OptionsFileLine) :-
             throw(options_file_error(
                 "expected `=', `:=' or `+=' after `" ++ VarName ++ "'"))
         ),
-        list.takewhile(char.is_whitespace, Line4, _, VarValue),
+        list.drop_while(char.is_whitespace, Line4, VarValue),
         OptionsFileLine = define_variable(VarName, Add, VarValue)
     ).
 
@@ -638,7 +638,7 @@ parse_variable(VarName, Chars0, Chars) :-
     parse_variable_2(yes, [], VarList, Chars0, Chars),
     string.from_rev_char_list(VarList, VarName),
     ( if VarName = "" then
-        list.takewhile(isnt(char.is_whitespace), Chars, FirstWord, _),
+        list.take_while(isnt(char.is_whitespace), Chars, FirstWord),
         throw(options_file_error("expected variable at `" ++
             string.from_char_list(FirstWord) ++ "'"))
     else
@@ -758,7 +758,7 @@ split_into_words(Chars) = list.reverse(split_into_words_2(Chars, [])).
 :- func split_into_words_2(list(char), list(string)) = list(string).
 
 split_into_words_2(Chars0, RevWords0) = RevWords :-
-    list.takewhile(char.is_whitespace, Chars0, _, Chars1),
+    list.drop_while(char.is_whitespace, Chars0, Chars1),
     (
         Chars1 = [],
         RevWords = RevWords0
diff --git a/compiler/structure_reuse.direct.choose_reuse.m b/compiler/structure_reuse.direct.choose_reuse.m
index 6de027a..0c88fe6 100644
--- a/compiler/structure_reuse.direct.choose_reuse.m
+++ b/compiler/structure_reuse.direct.choose_reuse.m
@@ -1377,7 +1377,7 @@ dump_match(Prefix, Match, !IO) :-
 dump_match_details(Match, !IO) :-
     Conds = list.map((func(DeconSpec) = DeconSpec ^ decon_conds),
         Match ^ decon_specs),
-    ( if list.takewhile(reuse_as_all_unconditional_reuses, Conds, _, []) then
+    ( if all_true(reuse_as_all_unconditional_reuses, Conds) then
         CondsString = "A"
     else
         CondsString = "C"
diff --git a/compiler/structure_reuse.domain.m b/compiler/structure_reuse.domain.m
index 28bbc22..98a544c 100644
--- a/compiler/structure_reuse.domain.m
+++ b/compiler/structure_reuse.domain.m
@@ -472,8 +472,8 @@ reuse_as_subsumed_by(ModuleInfo, ProcInfo, FirstReuseAs, SecondReuseAs) :-
     ;
         FirstReuseAs = conditional(ReuseConditionsFirst),
         SecondReuseAs = conditional(ReuseConditionsSecond),
-        list.takewhile(reuse_conditions_subsume_reuse_condition(ModuleInfo,
-            ProcInfo, ReuseConditionsSecond), ReuseConditionsFirst, _,
+        list.drop_while(reuse_conditions_subsume_reuse_condition(ModuleInfo,
+            ProcInfo, ReuseConditionsSecond), ReuseConditionsFirst,
             NotSubsumed),
         NotSubsumed = []
     ).
diff --git a/compiler/structure_sharing.domain.m b/compiler/structure_sharing.domain.m
index 43540e0..fc1b994 100644
--- a/compiler/structure_sharing.domain.m
+++ b/compiler/structure_sharing.domain.m
@@ -495,8 +495,8 @@ sharing_from_unification(ModuleInfo, ProcInfo, Unification, GoalInfo)
     (
         Unification = construct(Var, ConsId, Args0, _, _, _, _),
         ( if var_needs_sharing_analysis(ModuleInfo, ProcInfo, Var) then
-            list.takewhile(is_introduced_typeinfo_arg(ProcInfo), Args0,
-                _TypeInfoArgs, Args),
+            list.drop_while(is_introduced_typeinfo_arg(ProcInfo), Args0,
+                Args),
             number_args(Args, NumberedArgs),
             some [!SharingSet] (
                 !:SharingSet = sharing_set_init,
@@ -512,8 +512,8 @@ sharing_from_unification(ModuleInfo, ProcInfo, Unification, GoalInfo)
         )
     ;
         Unification = deconstruct(Var, ConsId, Args0, _, _, _),
-        list.takewhile(is_introduced_typeinfo_arg(ProcInfo), Args0,
-            _TypeInfoArgs, Args),
+        list.drop_while(is_introduced_typeinfo_arg(ProcInfo), Args0,
+            Args),
         number_args(Args, NumberedArgs),
         optimize_for_deconstruct(GoalInfo, NumberedArgs, ReducedNumberedArgs),
         some [!SharingSet] (
diff --git a/compiler/term_constr_data.m b/compiler/term_constr_data.m
index ae35dd1..4eb79a1 100644
--- a/compiler/term_constr_data.m
+++ b/compiler/term_constr_data.m
@@ -526,7 +526,7 @@ flatten_conjuncts(Goals0 @ [_, _ | _], Goals) :-
 flatten_conjuncts_2([], !RevGoals).
 flatten_conjuncts_2([Goal0 | Goals0], !RevGoals) :-
     ( if Goal0 = term_primitive(_, _, _) then
-        list.takewhile(is_primitive, Goals0, Primitives, NextNonPrimitive),
+        list.split_while(is_primitive, Goals0, Primitives, NextNonPrimitive),
         (
             Primitives = [],
             NewPrimitive = Goal0
diff --git a/compiler/write_deps_file.m b/compiler/write_deps_file.m
index e661e06..b38b139 100644
--- a/compiler/write_deps_file.m
+++ b/compiler/write_deps_file.m
@@ -974,7 +974,7 @@ generate_dependencies_write_d_files(Globals, [Dep | Deps],
         FindModule = (pred(OtherModule::in) is semidet :-
             ModuleName \= OtherModule
         ),
-        list.takewhile(FindModule, TransOptOrder, _, TransOptDeps0),
+        list.drop_while(FindModule, TransOptOrder, TransOptDeps0),
         ( if TransOptDeps0 = [_ | TransOptDeps1] then
             % The module was found in the list.
             TransOptDeps = TransOptDeps1
diff --git a/compiler/xml_documentation.m b/compiler/xml_documentation.m
index 338f070..4c8e2d9 100644
--- a/compiler/xml_documentation.m
+++ b/compiler/xml_documentation.m
@@ -148,8 +148,8 @@ build_comments(S, comments(!.C), comments(!:C), !IO) :-
 :- func line_type(list(character)) = line_type.
 
 line_type(Line) = LineType :-
-    list.takewhile(char.is_whitespace, Line, _WhiteSpace, Rest),
-    list.takewhile(is_not_comment_char, Rest, Decl, Comment),
+    list.drop_while(char.is_whitespace, Line, Rest),
+    list.split_while(is_not_comment_char, Rest, Decl, Comment),
     (
         Rest = [],
         LineType = blank
diff --git a/deep_profiler/read_profile.m b/deep_profiler/read_profile.m
index fd11a91..884491e 100644
--- a/deep_profiler/read_profile.m
+++ b/deep_profiler/read_profile.m
@@ -823,7 +823,7 @@ add_plus_one_for_function(pf_predicate) = "".
 fix_type_spec_suffix(Chars0, Chars, SpecInfoStr) :-
     ( if Chars0 = ['_', '_', '[' | SpecInfo0 ] then
         Chars = [],
-        list.takewhile(non_right_bracket, SpecInfo0, SpecInfo, _),
+        list.take_while(non_right_bracket, SpecInfo0, SpecInfo),
         string.from_char_list(SpecInfo, SpecInfoStr)
     else if Chars0 = [Char | TailChars0] then
         fix_type_spec_suffix(TailChars0, TailChars, SpecInfoStr),
diff --git a/deep_profiler/top_procs.m b/deep_profiler/top_procs.m
index f76ef8d..7f4b660 100644
--- a/deep_profiler/top_procs.m
+++ b/deep_profiler/top_procs.m
@@ -105,7 +105,7 @@ find_top_procs(Sort, InclDesc, Scope, Limit, Deep) = MaybeTopPSIs :-
                 ThresholdPred = (pred(PSI::in) is semidet :-
                     RawThresholdPred(Deep, Threshold, PSI)
                 ),
-                list.takewhile(ThresholdPred, DescendingPSIs, TopPSIs, _),
+                list.take_while(ThresholdPred, DescendingPSIs, TopPSIs),
                 MaybeTopPSIs = ok(TopPSIs)
             )
         ;
@@ -120,7 +120,7 @@ find_top_procs(Sort, InclDesc, Scope, Limit, Deep) = MaybeTopPSIs :-
                 ThresholdPred = (pred(PSI::in) is semidet :-
                     RawThresholdPred(Deep, Threshold, PSI)
                 ),
-                list.takewhile(ThresholdPred, DescendingPSIs, TopPSIs, _),
+                list.take_while(ThresholdPred, DescendingPSIs, TopPSIs),
                 MaybeTopPSIs = ok(TopPSIs)
             )
         )
diff --git a/library/list.m b/library/list.m
index 9565434..a90f95b 100644
--- a/library/list.m
+++ b/library/list.m
@@ -230,6 +230,22 @@
 :- pred split_upto(int::in, list(T)::in, list(T)::out, list(T)::out)
     is det.
 
+    % split_while(Predicate, List, UptoList, AfterList) takes a
+    % closure with one input argument, and calls it on successive members
+    % of List as long as the calls succeed. The elements for which
+    % the call succeeds are placed in UptoList and the first element for
+    % which the call fails, and all the remaining elements of List are
+    % placed in AfterList.
+    %
+:- pred split_while(pred(T)::in(pred(in) is semidet), list(T)::in,
+    list(T)::out, list(T)::out) is det.
+
+    % takewhile/4 is the old name for split_while/4.
+    %
+:- pragma obsolete(takewhile/4).
+:- pred takewhile(pred(T)::in(pred(in) is semidet), list(T)::in,
+    list(T)::out, list(T)::out) is det.
+
     % take(Len, List, Start):
     %
     % `Start' is the first `Len' elements of `List'. Fails if `List' has
@@ -251,6 +267,15 @@
 :- pred take_upto(int::in, list(T)::in, list(T)::out) is det.
 :- func take_upto(int, list(T)) = list(T).
 
+    % take_while(Pred, List, Start):
+    %
+    % 'Start' is the first elements of 'List' that satisfy 'Pred'.
+    %
+:- pred take_while(pred(T)::in(pred(in) is semidet), list(T)::in,
+    list(T)::out) is det.
+:- func take_while(pred(T), list(T)) = list(T).
+:- mode take_while(pred(in) is semidet, in) = out is det.
+
     % drop(Len, List, End):
     %
     % `End' is the remainder of `List' after removing the first `Len' elements.
@@ -267,6 +292,16 @@
     %
 :- pred det_drop(int::in, list(T)::in, list(T)::out) is det.
 
+    % drop_while(Pred, List, End):
+    %
+    % Drop items that satisfy 'Pred' from the head of 'List' leaving only
+    % 'End'.
+    %
+:- pred drop_while(pred(T)::in(pred(in) is semidet), list(T)::in,
+    list(T)::out) is det.
+:- func drop_while(pred(T), list(T)) = list(T).
+:- mode drop_while(pred(in) is semidet, in) = out is det.
+
     % insert(Elem, List0, List):
     %
     % `List' is the result of inserting `Elem' somewhere in `List0'.
@@ -1632,16 +1667,6 @@
 :- pred find_index_of_match(pred(T), list(T), int, int).
 :- mode find_index_of_match(pred(in) is semidet, in, in, out) is semidet.
 
-    % takewhile(Predicate, List, UptoList, AfterList) takes a
-    % closure with one input argument, and calls it on successive members
-    % of List as long as the calls succeed. The elements for which
-    % the call succeeds are placed in UptoList and the first element for
-    % which the call fails, and all the remaining elements of List are
-    % placed in AfterList.
-    %
-:- pred takewhile(pred(T)::in(pred(in) is semidet), list(T)::in,
-    list(T)::out, list(T)::out) is det.
-
 %---------------------------------------------------------------------------%
 
     % sort(Compare, Unsorted, Sorted) is true iff Sorted is a
@@ -2313,6 +2338,19 @@ list.split_upto(N, List, Start, End) :-
         End = List
     ).
 
+split_while(_, [], [], []).
+split_while(P, [X | Xs], Ins, Outs) :-
+    ( if P(X) then
+        Ins = [X | Ins0],
+        split_while(P, Xs, Ins0, Outs)
+    else
+        Ins = [],
+        Outs = [X | Xs]
+    ).
+
+takewhile(P, Xs, Ins, Outs) :-
+    split_while(P, Xs, Ins, Outs).
+
 list.take(N, Xs, InitialXs) :-
     ( if N > 0 then
         Xs = [HeadX | TailXs],
@@ -2339,6 +2377,18 @@ list.take_upto(N, Xs, InitialXs) :-
         InitialXs = Xs
     ).
 
+take_while(_, [], []).
+take_while(P, [X | Xs], Start) :-
+    ( if P(X) then
+        take_while(P, Xs, Start0),
+        Start = [X | Start0]
+    else
+        Start = []
+    ).
+
+take_while(P, Xs) = Start :-
+    take_while(P, Xs, Start).
+
 list.drop(N, Xs, FinalXs) :-
     ( if N > 0 then
         Xs = [_ | Tail],
@@ -2360,6 +2410,17 @@ list.det_drop(N, Xs, FinalXs) :-
         FinalXs = Xs
     ).
 
+drop_while(_, [], []).
+drop_while(P, [X | Xs], End) :-
+    ( if P(X) then
+        drop_while(P, Xs, End)
+    else
+        End = [X | Xs]
+    ).
+
+drop_while(P, Xs) = End :-
+    drop_while(P, Xs, End).
+
 %---------------------------------------------------------------------------%
 
 list.duplicate(N, X) = Xs :-
@@ -3066,16 +3127,6 @@ list.find_index_of_match(Match, [X | Xs], Index0, Index) :-
 
 %---------------------------------------------------------------------------%
 
-list.takewhile(_, [], [], []).
-list.takewhile(P, [X | Xs], Ins, Outs) :-
-    ( if P(X) then
-        Ins = [X | Ins0],
-        list.takewhile(P, Xs, Ins0, Outs)
-    else
-        Ins = [],
-        Outs = [X | Xs]
-    ).
-
 list.sort_and_remove_dups(P, L0, L) :-
     list.sort(P, L0, L1),
     list.remove_adjacent_dups(P, L1, L).
-- 
2.8.0.rc3



More information about the reviews mailing list