Skip to content

Commit

Permalink
Make final sort determinist
Browse files Browse the repository at this point in the history
  • Loading branch information
xvw committed Sep 24, 2024
1 parent c3e9c69 commit cc4b4f2
Show file tree
Hide file tree
Showing 3 changed files with 41 additions and 37 deletions.
6 changes: 5 additions & 1 deletion src/analysis/type_search.ml
Original file line number Diff line number Diff line change
Expand Up @@ -84,7 +84,11 @@ let compare_result Query_protocol.{ cost = cost_a; name = a; doc = doc_a; _ }
match (c, doc_a, doc_b) with
| 0, Some _, None -> 1
| 0, None, Some _ -> -1
| 0, Some a, Some b -> Int.compare (String.length a) (String.length b)
| 0, Some doc_a, Some doc_b ->
let c = Int.compare (String.length doc_a) (String.length doc_b) in
(* Make default insertion determinist *)
if Int.equal 0 c then String.compare a b else c
| 0, None, None -> String.compare a b
| _ -> c
else c

Expand Down
20 changes: 10 additions & 10 deletions tests/test-dirs/search-by-type-comparison-to-polarity-search.t
Original file line number Diff line number Diff line change
Expand Up @@ -16,14 +16,14 @@ potential failures, so lifting the result in an int option).
"name": "int_of_string_opt",
"type": "string -> int option"
}
{
"name": "Int64.of_string_opt",
"type": "string -> int64 option"
}
{
"name": "Int32.of_string_opt",
"type": "string -> int32 option"
}
{
"name": "Int64.of_string_opt",
"type": "string -> int64 option"
}
{
"name": "Sys.getenv_opt",
"type": "string -> string option"
Expand Down Expand Up @@ -132,17 +132,17 @@ map).
"name": "Seq.map",
"type": "('a -> 'b) -> 'a Stdlib__Seq.t -> 'b Stdlib__Seq.t"
}
{
"name": "List.filter_map",
"type": "('a -> 'b option) -> 'a list -> 'b list"
}
{
"name": "List.concat_map",
"type": "('a -> 'b list) -> 'a list -> 'b list"
}
{
"name": "ListLabels.filter_map",
"type": "f:('a -> 'b option) -> 'a list -> 'b list"
"name": "List.filter_map",
"type": "('a -> 'b option) -> 'a list -> 'b list"
}
{
"name": "ListLabels.concat_map",
"type": "f:('a -> 'b list) -> 'a list -> 'b list"
}


Expand Down
52 changes: 26 additions & 26 deletions tests/test-dirs/search-by-type.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -14,14 +14,14 @@
"doc": null
}
{
"name": "Int64.of_string_opt",
"type": "string -> int64 option",
"name": "Int32.of_string_opt",
"type": "string -> int32 option",
"cost": 2,
"doc": null
}
{
"name": "Int32.of_string_opt",
"type": "string -> int32 option",
"name": "Int64.of_string_opt",
"type": "string -> int64 option",
"cost": 2,
"doc": null
}
Expand Down Expand Up @@ -109,20 +109,20 @@
"doc": null
}
{
"name": "List.filter_map",
"type": "('a -> 'b option) -> 'a list -> 'b list",
"name": "List.concat_map",
"type": "('a -> 'b list) -> 'a list -> 'b list",
"cost": 10,
"doc": null
}
{
"name": "List.concat_map",
"type": "('a -> 'b list) -> 'a list -> 'b list",
"name": "List.filter_map",
"type": "('a -> 'b option) -> 'a list -> 'b list",
"cost": 10,
"doc": null
}
{
"name": "ListLabels.filter_map",
"type": "f:('a -> 'b option) -> 'a list -> 'b list",
"name": "ListLabels.concat_map",
"type": "f:('a -> 'b list) -> 'a list -> 'b list",
"cost": 10,
"doc": null
}
Expand Down Expand Up @@ -234,34 +234,34 @@
{
"file": "moreLabels.mli",
"start": {
"line": 168,
"line": 318,
"col": 2
},
"end": {
"line": 168,
"col": 55
"line": 318,
"col": 52
},
"name": "MoreLabels.Hashtbl.replace",
"type": "('a, 'b) Stdlib__MoreLabels.Hashtbl.t -> key:'a -> data:'b -> unit",
"name": "MoreLabels.Hashtbl.add_seq",
"type": "('a, 'b) Stdlib__MoreLabels.Hashtbl.t -> ('a * 'b) Seq.t -> unit",
"cost": 48,
"doc": null,
"constructible": "MoreLabels.Hashtbl.replace _ ~key:_ ~data:_"
"constructible": "MoreLabels.Hashtbl.add_seq _ _"
},
{
"file": "moreLabels.mli",
"start": {
"line": 318,
"line": 168,
"col": 2
},
"end": {
"line": 318,
"col": 52
"line": 168,
"col": 55
},
"name": "MoreLabels.Hashtbl.add_seq",
"type": "('a, 'b) Stdlib__MoreLabels.Hashtbl.t -> ('a * 'b) Seq.t -> unit",
"name": "MoreLabels.Hashtbl.replace",
"type": "('a, 'b) Stdlib__MoreLabels.Hashtbl.t -> key:'a -> data:'b -> unit",
"cost": 48,
"doc": null,
"constructible": "MoreLabels.Hashtbl.add_seq _ _"
"constructible": "MoreLabels.Hashtbl.replace _ ~key:_ ~data:_"
},
{
"file": "moreLabels.mli",
Expand Down Expand Up @@ -316,14 +316,14 @@
"doc": "Convert the given string to an integer. The string is read in decimal (by default, or if the string begins with [0u]), in hexadecimal (if it begins with [0x] or [0X]), in octal (if it begins with [0o] or [0O]), or in binary (if it begins with [0b] or [0B]). The [0u] prefix reads the input as an unsigned integer in the range [[0, 2*max_int+1]]. If the input exceeds {!max_int} it is converted to the signed integer [min_int + input - max_int - 1]. The [_] (underscore) character can appear anywhere in the string and is ignored. Return [None] if the given string is not a valid representation of an integer, or if the integer represented exceeds the range of integers representable in type [int]. @since 4.05"
}
{
"name": "Int64.of_string_opt",
"type": "string -> int64 option",
"name": "Int32.of_string_opt",
"type": "string -> int32 option",
"cost": 2,
"doc": "Same as [of_string], but return [None] instead of raising. @since 4.05"
}
{
"name": "Int32.of_string_opt",
"type": "string -> int32 option",
"name": "Int64.of_string_opt",
"type": "string -> int64 option",
"cost": 2,
"doc": "Same as [of_string], but return [None] instead of raising. @since 4.05"
}
Expand Down

0 comments on commit cc4b4f2

Please sign in to comment.