Skip to content

Commit

Permalink
Code review
Browse files Browse the repository at this point in the history
  • Loading branch information
mshinwell committed Mar 6, 2019
1 parent 437353f commit d2b62c9
Show file tree
Hide file tree
Showing 2 changed files with 11 additions and 23 deletions.
24 changes: 6 additions & 18 deletions utils/misc.ml
Expand Up @@ -156,9 +156,7 @@ module Stdlib = struct
| [], [] -> true
| _::_, [] -> false
| [], _::_ -> true
| x1::t, x2::of_ ->
if equal x1 x2 then is_prefix ~equal t ~of_
else false
| x1::t, x2::of_ -> equal x1 x2 && is_prefix ~equal t ~of_

type 'a longest_common_prefix_result = {
longest_common_prefix : 'a list;
Expand All @@ -169,24 +167,14 @@ module Stdlib = struct
let find_and_chop_longest_common_prefix ~equal ~first ~second =
let rec find_prefix ~longest_common_prefix_rev l1 l2 =
match l1, l2 with
| [], []
| [], _::_
| _::_, [] ->
let longest_common_prefix = List.rev longest_common_prefix_rev in
{ longest_common_prefix;
| elt1 :: l1, elt2 :: l2 when equal elt1 elt2 ->
let longest_common_prefix_rev = elt1 :: longest_common_prefix_rev in
find_prefix ~longest_common_prefix_rev l1 l2
| l1, l2 ->
{ longest_common_prefix = List.rev longest_common_prefix_rev;
first_without_longest_common_prefix = l1;
second_without_longest_common_prefix = l2;
}
| elt1::l1_tail, elt2::l2_tail ->
if equal elt1 elt2 then
let longest_common_prefix_rev = elt1 :: longest_common_prefix_rev in
find_prefix ~longest_common_prefix_rev l1_tail l2_tail
else
let longest_common_prefix = List.rev longest_common_prefix_rev in
{ longest_common_prefix;
first_without_longest_common_prefix = l1;
second_without_longest_common_prefix = l2;
}
in
find_prefix ~longest_common_prefix_rev:[] first second
end
Expand Down
10 changes: 5 additions & 5 deletions utils/misc.mli
Expand Up @@ -117,28 +117,28 @@ module Stdlib : sig
the [n] first elements of [l] and [after] the remaining ones.
If [l] has less than [n] elements, raises Invalid_argument. *)

(** Returns [true] iff the given list, with respect to the given equality
function on list members, is a prefix of the list [of_]. *)
val is_prefix
: equal:('a -> 'a -> bool)
-> 'a list
-> of_:'a list
-> bool
(** Returns [true] iff the given list, with respect to the given equality
function on list members, is a prefix of the list [of_]. *)

type 'a longest_common_prefix_result = private {
longest_common_prefix : 'a list;
first_without_longest_common_prefix : 'a list;
second_without_longest_common_prefix : 'a list;
}

(** Returns the longest list that, with respect to the provided equality
function, is a prefix of both of the given lists. The input lists,
each with such longest common prefix removed, are also returned. *)
val find_and_chop_longest_common_prefix
: equal:('a -> 'a -> bool)
-> first:'a list
-> second:'a list
-> 'a longest_common_prefix_result
(** Returns the longest list that, with respect to the provided equality
function, is a prefix of both of the given lists. The input lists,
each with such longest common prefix removed, are also returned. *)
end

module Option : sig
Expand Down

0 comments on commit d2b62c9

Please sign in to comment.