ocaml/testsuite/tests/lib-set/testmap.ml

254 lines
6.8 KiB
OCaml
Raw Normal View History

2017-12-02 14:23:09 -08:00
(* TEST
*)
module M = Map.Make(struct type t = int let compare (x:t) y = compare x y end)
let img x m = try Some(M.find x m) with Not_found -> None
let testvals = [0;1;2;3;4;5;6;7;8;9]
let check msg cond =
if not (List.for_all cond testvals) then
Printf.printf "Test %s FAILED\n%!" msg
let checkbool msg b =
if not b then
Printf.printf "Test %s FAILED\n%!" msg
let uncurry (f: 'a -> 'b -> 'c) (x, y: 'a * 'b) : 'c = f x y
let test x v s1 s2 =
checkbool "is_empty"
(M.is_empty s1 = List.for_all (fun i -> img i s1 = None) testvals);
check "mem"
(fun i -> M.mem i s1 = (img i s1 <> None));
check "add"
(let s = M.add x v s1 in
fun i -> img i s = (if i = x then Some v else img i s1));
check "singleton"
(let s = M.singleton x v in
fun i -> img i s = (if i = x then Some v else None));
check "remove"
(let s = M.remove x s1 in
fun i -> img i s = (if i = x then None else img i s1));
check "merge-union"
(let f _ o1 o2 =
match o1, o2 with
| Some v1, Some v2 -> Some (v1 +. v2)
| None, _ -> o2
| _, None -> o1 in
let s = M.merge f s1 s2 in
fun i -> img i s = f i (img i s1) (img i s2));
check "merge-inter"
(let f _ o1 o2 =
match o1, o2 with
| Some v1, Some v2 -> Some (v1 -. v2)
| _, _ -> None in
let s = M.merge f s1 s2 in
fun i -> img i s = f i (img i s1) (img i s2));
checkbool "bindings"
(let rec extract = function
| [] -> []
| hd :: tl ->
match img hd s1 with
| None -> extract tl
| Some v ->(hd, v) :: extract tl in
M.bindings s1 = extract testvals);
checkbool "for_all"
(let p x y = x mod 2 = 0 in
M.for_all p s1 = List.for_all (uncurry p) (M.bindings s1));
checkbool "exists"
(let p x y = x mod 3 = 0 in
M.exists p s1 = List.exists (uncurry p) (M.bindings s1));
checkbool "filter"
(let p x y = x >= 3 && x <= 6 in
M.bindings(M.filter p s1) = List.filter (uncurry p) (M.bindings s1));
2020-03-14 07:09:30 -07:00
checkbool "filter_map"
(let f x y = if x >= 3 && x <= 6 then Some (2 * x) else None in
let f_on_pair (x, y) = Option.map (fun v -> (x, v)) (f x y) in
M.bindings(M.filter_map f s1) = List.filter_map f_on_pair (M.bindings s1));
checkbool "partition"
(let p x y = x >= 3 && x <= 6 in
let (st,sf) = M.partition p s1
and (lt,lf) = List.partition (uncurry p) (M.bindings s1) in
M.bindings st = lt && M.bindings sf = lf);
checkbool "cardinal"
(M.cardinal s1 = List.length (M.bindings s1));
checkbool "min_binding"
(try
let (k,v) = M.min_binding s1 in
img k s1 = Some v && M.for_all (fun i _ -> k <= i) s1
with Not_found ->
M.is_empty s1);
checkbool "max_binding"
(try
let (k,v) = M.max_binding s1 in
img k s1 = Some v && M.for_all (fun i _ -> k >= i) s1
with Not_found ->
M.is_empty s1);
checkbool "choose"
(try
let (x,v) = M.choose s1 in img x s1 = Some v
with Not_found ->
M.is_empty s1);
checkbool "find_first"
(let (l, p, r) = M.split x s1 in
if p = None && M.is_empty r then
try
let _ = M.find_first (fun k -> k >= x) s1 in
false
with Not_found ->
true
else
let (k, v) = M.find_first (fun k -> k >= x) s1 in
match p with
None -> (k, v) = M.min_binding r
| Some v1 -> (k, v) = (x, v1));
checkbool "find_first_opt"
(let (l, p, r) = M.split x s1 in
Do not disable warnings by default when compiling tests (#1293) Before this comit, the tests using Makefile.several were compiled with all the compiler warnings turned off. This commit gets rid of this behaviour. Doing so revealed a number of warnings which are listed below. Directory testsuite/tests/basic: File "eval_order_5.ml", line 3, characters 16-22: Warning 5: this function application is partial, maybe some arguments are missing. Here the warning can't be avoided so the code has been modified to disable just this specific warning, locally. File "pr6322.ml", line 10, characters 2-15: Warning 3: deprecated: String.set Code updated to not use this operator any more. Directory testsuite/tests/basic-float: File "tfloat_record.ml", line 35, characters 8-53: Warning 55: Cannot inline: Function information unavailable Since the inline attribute cannot be applied and since this does not seem to be relevant for the test, this commit fixes the warning by getting rid of the attribute itself. Directory tests/basic-more: File morematch.ml has several warnings that are expected and have been ignored locally. File "sequential_and_or.ml", line 21, characters 2-17: Warning 3: deprecated: String.set Use Bytes.set instead. Done. The use of String.set was not relevant for the test. File "tformat.ml", line 15, characters 2-16: Warning 3: deprecated: Format.bprintf Given that the function is deprecated, the corresponding test has simply been removed. Directory tests/lib-bigarray: File "pr5115.ml", line 11, characters 2-11: Warning 10: this expression should have type unit. Given that the warning seems legitimate, add a call to ignore. Directory tests/lib-buffer: File "test.ml", line 42, characters 21-38: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) File "test.ml", line 52, characters 21-38: [same warning] File "test.ml", line 66, characters 21-38: [same warning] This warnign has been fixed by making the code able to handle any string used as argument of the Invalid_argument constructor. Directory tests/lib-set: File "testmap.ml", line 125, characters 10-21: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: None File "testmap.ml", line 151, characters 10-21: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: None These warnings were legitimate. One case was not taken into account. The code has been fixed. File "testset.ml", line 137, characters 10-16: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: None File "testset.ml", line 165, characters 10-16: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: None Same remark here. In directory tests/lib-stack: File "test.ml", line 110, characters 27-29: Warning 26: unused variable s2. Legitimate warning. Code fixed. In directory tests/lib-str: File "t01.ml", line 1068, characters 26-45: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) Legitimate warning. Code fixed. Directory tests/lib-threads: File "backtrace_threads.ml", line 7, characters 7-40: Warning 21: this statement never returns (or has an unsound type.) Legitimate warning. Code fixed. File "close.ml", line 10, characters 12-25: Warning 3: deprecated: String.create Use Bytes.create instead. Legitimate warning. Code fixed. File "fileio.ml", line 22, characters 15-28: Warning 3: deprecated: String.create Use Bytes.create instead. File "fileio.ml", line 36, characters 15-28: Warning 3: deprecated: String.create Use Bytes.create instead. Warnings legitimate. Code fixed. Directory tests/match-exception: File "match_failure.ml", line 9, characters 12-199: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: Some _ (However, some guarded clause may match this value.) This code must produce this warning so make sure it is locally ignored. Directory tests/misc: File "ephetest3.ml", line 99, characters 19-31: Warning 3: deprecated: Array.create Use Array.make instead. Legitimate warning. Code fixed. File "sorts.ml", line 131, characters 10-23: Warning 3: deprecated: String.create Use Bytes.create instead. Legitimate warning. Code fixed. File "sorts.ml", line 133, characters 4-38: Warning 3: deprecated: String.set Use Bytes.set instead. Legitimate warning. Code fixed. File "sorts.ml", line 4237, characters 15-24: Warning 3: deprecated: Sort.list Use List.sort instead. Test removed. File "sorts.ml", line 4373, characters 10-23: Warning 3: deprecated: String.create Use Bytes.create instead. Legitimate warning. Code fixed. File "sorts.ml", line 4408, characters 34-44: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4408, characters 45-55: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4431, characters 22-32: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4432, characters 22-32: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4433, characters 22-32: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4450, characters 21-31: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. Directory tests/misc-unsafe: File "almabench.ml", line 239, characters 20-22: Warning 3: deprecated: Pervasives.or Use (||) instead. Legitimate warning. Code fixed. File "soli.ml", line 38, characters 12-24: Warning 3: deprecated: Array.create Use Array.make instead. Legitimate warning. Code fixed. Directory tests/prim-bigstring: File "bigstring_access.ml", line 34, characters 23-46: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) File "bigstring_access.ml", line 41, characters 23-46: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) File "string_access.ml", line 21, characters 23-46: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) File "string_access.ml", line 28, characters 23-46: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) Legitimate warnings. Fixed by accepting any string as argument of the Invalid_argument constructor rather than just "index out of bounds".
2017-08-17 02:10:30 -07:00
let find_first_opt_result = M.find_first_opt (fun k -> k >= x) s1 in
if p = None && M.is_empty r then
Do not disable warnings by default when compiling tests (#1293) Before this comit, the tests using Makefile.several were compiled with all the compiler warnings turned off. This commit gets rid of this behaviour. Doing so revealed a number of warnings which are listed below. Directory testsuite/tests/basic: File "eval_order_5.ml", line 3, characters 16-22: Warning 5: this function application is partial, maybe some arguments are missing. Here the warning can't be avoided so the code has been modified to disable just this specific warning, locally. File "pr6322.ml", line 10, characters 2-15: Warning 3: deprecated: String.set Code updated to not use this operator any more. Directory testsuite/tests/basic-float: File "tfloat_record.ml", line 35, characters 8-53: Warning 55: Cannot inline: Function information unavailable Since the inline attribute cannot be applied and since this does not seem to be relevant for the test, this commit fixes the warning by getting rid of the attribute itself. Directory tests/basic-more: File morematch.ml has several warnings that are expected and have been ignored locally. File "sequential_and_or.ml", line 21, characters 2-17: Warning 3: deprecated: String.set Use Bytes.set instead. Done. The use of String.set was not relevant for the test. File "tformat.ml", line 15, characters 2-16: Warning 3: deprecated: Format.bprintf Given that the function is deprecated, the corresponding test has simply been removed. Directory tests/lib-bigarray: File "pr5115.ml", line 11, characters 2-11: Warning 10: this expression should have type unit. Given that the warning seems legitimate, add a call to ignore. Directory tests/lib-buffer: File "test.ml", line 42, characters 21-38: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) File "test.ml", line 52, characters 21-38: [same warning] File "test.ml", line 66, characters 21-38: [same warning] This warnign has been fixed by making the code able to handle any string used as argument of the Invalid_argument constructor. Directory tests/lib-set: File "testmap.ml", line 125, characters 10-21: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: None File "testmap.ml", line 151, characters 10-21: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: None These warnings were legitimate. One case was not taken into account. The code has been fixed. File "testset.ml", line 137, characters 10-16: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: None File "testset.ml", line 165, characters 10-16: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: None Same remark here. In directory tests/lib-stack: File "test.ml", line 110, characters 27-29: Warning 26: unused variable s2. Legitimate warning. Code fixed. In directory tests/lib-str: File "t01.ml", line 1068, characters 26-45: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) Legitimate warning. Code fixed. Directory tests/lib-threads: File "backtrace_threads.ml", line 7, characters 7-40: Warning 21: this statement never returns (or has an unsound type.) Legitimate warning. Code fixed. File "close.ml", line 10, characters 12-25: Warning 3: deprecated: String.create Use Bytes.create instead. Legitimate warning. Code fixed. File "fileio.ml", line 22, characters 15-28: Warning 3: deprecated: String.create Use Bytes.create instead. File "fileio.ml", line 36, characters 15-28: Warning 3: deprecated: String.create Use Bytes.create instead. Warnings legitimate. Code fixed. Directory tests/match-exception: File "match_failure.ml", line 9, characters 12-199: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: Some _ (However, some guarded clause may match this value.) This code must produce this warning so make sure it is locally ignored. Directory tests/misc: File "ephetest3.ml", line 99, characters 19-31: Warning 3: deprecated: Array.create Use Array.make instead. Legitimate warning. Code fixed. File "sorts.ml", line 131, characters 10-23: Warning 3: deprecated: String.create Use Bytes.create instead. Legitimate warning. Code fixed. File "sorts.ml", line 133, characters 4-38: Warning 3: deprecated: String.set Use Bytes.set instead. Legitimate warning. Code fixed. File "sorts.ml", line 4237, characters 15-24: Warning 3: deprecated: Sort.list Use List.sort instead. Test removed. File "sorts.ml", line 4373, characters 10-23: Warning 3: deprecated: String.create Use Bytes.create instead. Legitimate warning. Code fixed. File "sorts.ml", line 4408, characters 34-44: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4408, characters 45-55: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4431, characters 22-32: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4432, characters 22-32: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4433, characters 22-32: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4450, characters 21-31: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. Directory tests/misc-unsafe: File "almabench.ml", line 239, characters 20-22: Warning 3: deprecated: Pervasives.or Use (||) instead. Legitimate warning. Code fixed. File "soli.ml", line 38, characters 12-24: Warning 3: deprecated: Array.create Use Array.make instead. Legitimate warning. Code fixed. Directory tests/prim-bigstring: File "bigstring_access.ml", line 34, characters 23-46: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) File "bigstring_access.ml", line 41, characters 23-46: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) File "string_access.ml", line 21, characters 23-46: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) File "string_access.ml", line 28, characters 23-46: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) Legitimate warnings. Fixed by accepting any string as argument of the Invalid_argument constructor rather than just "index out of bounds".
2017-08-17 02:10:30 -07:00
match find_first_opt_result with
None -> true
| _ -> false
else
Do not disable warnings by default when compiling tests (#1293) Before this comit, the tests using Makefile.several were compiled with all the compiler warnings turned off. This commit gets rid of this behaviour. Doing so revealed a number of warnings which are listed below. Directory testsuite/tests/basic: File "eval_order_5.ml", line 3, characters 16-22: Warning 5: this function application is partial, maybe some arguments are missing. Here the warning can't be avoided so the code has been modified to disable just this specific warning, locally. File "pr6322.ml", line 10, characters 2-15: Warning 3: deprecated: String.set Code updated to not use this operator any more. Directory testsuite/tests/basic-float: File "tfloat_record.ml", line 35, characters 8-53: Warning 55: Cannot inline: Function information unavailable Since the inline attribute cannot be applied and since this does not seem to be relevant for the test, this commit fixes the warning by getting rid of the attribute itself. Directory tests/basic-more: File morematch.ml has several warnings that are expected and have been ignored locally. File "sequential_and_or.ml", line 21, characters 2-17: Warning 3: deprecated: String.set Use Bytes.set instead. Done. The use of String.set was not relevant for the test. File "tformat.ml", line 15, characters 2-16: Warning 3: deprecated: Format.bprintf Given that the function is deprecated, the corresponding test has simply been removed. Directory tests/lib-bigarray: File "pr5115.ml", line 11, characters 2-11: Warning 10: this expression should have type unit. Given that the warning seems legitimate, add a call to ignore. Directory tests/lib-buffer: File "test.ml", line 42, characters 21-38: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) File "test.ml", line 52, characters 21-38: [same warning] File "test.ml", line 66, characters 21-38: [same warning] This warnign has been fixed by making the code able to handle any string used as argument of the Invalid_argument constructor. Directory tests/lib-set: File "testmap.ml", line 125, characters 10-21: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: None File "testmap.ml", line 151, characters 10-21: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: None These warnings were legitimate. One case was not taken into account. The code has been fixed. File "testset.ml", line 137, characters 10-16: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: None File "testset.ml", line 165, characters 10-16: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: None Same remark here. In directory tests/lib-stack: File "test.ml", line 110, characters 27-29: Warning 26: unused variable s2. Legitimate warning. Code fixed. In directory tests/lib-str: File "t01.ml", line 1068, characters 26-45: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) Legitimate warning. Code fixed. Directory tests/lib-threads: File "backtrace_threads.ml", line 7, characters 7-40: Warning 21: this statement never returns (or has an unsound type.) Legitimate warning. Code fixed. File "close.ml", line 10, characters 12-25: Warning 3: deprecated: String.create Use Bytes.create instead. Legitimate warning. Code fixed. File "fileio.ml", line 22, characters 15-28: Warning 3: deprecated: String.create Use Bytes.create instead. File "fileio.ml", line 36, characters 15-28: Warning 3: deprecated: String.create Use Bytes.create instead. Warnings legitimate. Code fixed. Directory tests/match-exception: File "match_failure.ml", line 9, characters 12-199: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: Some _ (However, some guarded clause may match this value.) This code must produce this warning so make sure it is locally ignored. Directory tests/misc: File "ephetest3.ml", line 99, characters 19-31: Warning 3: deprecated: Array.create Use Array.make instead. Legitimate warning. Code fixed. File "sorts.ml", line 131, characters 10-23: Warning 3: deprecated: String.create Use Bytes.create instead. Legitimate warning. Code fixed. File "sorts.ml", line 133, characters 4-38: Warning 3: deprecated: String.set Use Bytes.set instead. Legitimate warning. Code fixed. File "sorts.ml", line 4237, characters 15-24: Warning 3: deprecated: Sort.list Use List.sort instead. Test removed. File "sorts.ml", line 4373, characters 10-23: Warning 3: deprecated: String.create Use Bytes.create instead. Legitimate warning. Code fixed. File "sorts.ml", line 4408, characters 34-44: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4408, characters 45-55: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4431, characters 22-32: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4432, characters 22-32: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4433, characters 22-32: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4450, characters 21-31: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. Directory tests/misc-unsafe: File "almabench.ml", line 239, characters 20-22: Warning 3: deprecated: Pervasives.or Use (||) instead. Legitimate warning. Code fixed. File "soli.ml", line 38, characters 12-24: Warning 3: deprecated: Array.create Use Array.make instead. Legitimate warning. Code fixed. Directory tests/prim-bigstring: File "bigstring_access.ml", line 34, characters 23-46: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) File "bigstring_access.ml", line 41, characters 23-46: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) File "string_access.ml", line 21, characters 23-46: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) File "string_access.ml", line 28, characters 23-46: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) Legitimate warnings. Fixed by accepting any string as argument of the Invalid_argument constructor rather than just "index out of bounds".
2017-08-17 02:10:30 -07:00
match find_first_opt_result with
| None -> false
| Some (k, v) ->
(match p with
| None -> (k, v) = M.min_binding r
| Some v1 -> (k, v) = (x, v1)));
checkbool "find_last"
(let (l, p, r) = M.split x s1 in
if p = None && M.is_empty l then
try
let _ = M.find_last (fun k -> k <= x) s1 in
false
with Not_found ->
true
else
let (k, v) = M.find_last (fun k -> k <= x) s1 in
match p with
None -> (k, v) = M.max_binding l
| Some v1 -> (k, v) = (x, v1));
checkbool "find_last_opt"
(let (l, p, r) = M.split x s1 in
Do not disable warnings by default when compiling tests (#1293) Before this comit, the tests using Makefile.several were compiled with all the compiler warnings turned off. This commit gets rid of this behaviour. Doing so revealed a number of warnings which are listed below. Directory testsuite/tests/basic: File "eval_order_5.ml", line 3, characters 16-22: Warning 5: this function application is partial, maybe some arguments are missing. Here the warning can't be avoided so the code has been modified to disable just this specific warning, locally. File "pr6322.ml", line 10, characters 2-15: Warning 3: deprecated: String.set Code updated to not use this operator any more. Directory testsuite/tests/basic-float: File "tfloat_record.ml", line 35, characters 8-53: Warning 55: Cannot inline: Function information unavailable Since the inline attribute cannot be applied and since this does not seem to be relevant for the test, this commit fixes the warning by getting rid of the attribute itself. Directory tests/basic-more: File morematch.ml has several warnings that are expected and have been ignored locally. File "sequential_and_or.ml", line 21, characters 2-17: Warning 3: deprecated: String.set Use Bytes.set instead. Done. The use of String.set was not relevant for the test. File "tformat.ml", line 15, characters 2-16: Warning 3: deprecated: Format.bprintf Given that the function is deprecated, the corresponding test has simply been removed. Directory tests/lib-bigarray: File "pr5115.ml", line 11, characters 2-11: Warning 10: this expression should have type unit. Given that the warning seems legitimate, add a call to ignore. Directory tests/lib-buffer: File "test.ml", line 42, characters 21-38: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) File "test.ml", line 52, characters 21-38: [same warning] File "test.ml", line 66, characters 21-38: [same warning] This warnign has been fixed by making the code able to handle any string used as argument of the Invalid_argument constructor. Directory tests/lib-set: File "testmap.ml", line 125, characters 10-21: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: None File "testmap.ml", line 151, characters 10-21: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: None These warnings were legitimate. One case was not taken into account. The code has been fixed. File "testset.ml", line 137, characters 10-16: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: None File "testset.ml", line 165, characters 10-16: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: None Same remark here. In directory tests/lib-stack: File "test.ml", line 110, characters 27-29: Warning 26: unused variable s2. Legitimate warning. Code fixed. In directory tests/lib-str: File "t01.ml", line 1068, characters 26-45: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) Legitimate warning. Code fixed. Directory tests/lib-threads: File "backtrace_threads.ml", line 7, characters 7-40: Warning 21: this statement never returns (or has an unsound type.) Legitimate warning. Code fixed. File "close.ml", line 10, characters 12-25: Warning 3: deprecated: String.create Use Bytes.create instead. Legitimate warning. Code fixed. File "fileio.ml", line 22, characters 15-28: Warning 3: deprecated: String.create Use Bytes.create instead. File "fileio.ml", line 36, characters 15-28: Warning 3: deprecated: String.create Use Bytes.create instead. Warnings legitimate. Code fixed. Directory tests/match-exception: File "match_failure.ml", line 9, characters 12-199: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: Some _ (However, some guarded clause may match this value.) This code must produce this warning so make sure it is locally ignored. Directory tests/misc: File "ephetest3.ml", line 99, characters 19-31: Warning 3: deprecated: Array.create Use Array.make instead. Legitimate warning. Code fixed. File "sorts.ml", line 131, characters 10-23: Warning 3: deprecated: String.create Use Bytes.create instead. Legitimate warning. Code fixed. File "sorts.ml", line 133, characters 4-38: Warning 3: deprecated: String.set Use Bytes.set instead. Legitimate warning. Code fixed. File "sorts.ml", line 4237, characters 15-24: Warning 3: deprecated: Sort.list Use List.sort instead. Test removed. File "sorts.ml", line 4373, characters 10-23: Warning 3: deprecated: String.create Use Bytes.create instead. Legitimate warning. Code fixed. File "sorts.ml", line 4408, characters 34-44: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4408, characters 45-55: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4431, characters 22-32: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4432, characters 22-32: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4433, characters 22-32: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4450, characters 21-31: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. Directory tests/misc-unsafe: File "almabench.ml", line 239, characters 20-22: Warning 3: deprecated: Pervasives.or Use (||) instead. Legitimate warning. Code fixed. File "soli.ml", line 38, characters 12-24: Warning 3: deprecated: Array.create Use Array.make instead. Legitimate warning. Code fixed. Directory tests/prim-bigstring: File "bigstring_access.ml", line 34, characters 23-46: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) File "bigstring_access.ml", line 41, characters 23-46: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) File "string_access.ml", line 21, characters 23-46: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) File "string_access.ml", line 28, characters 23-46: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) Legitimate warnings. Fixed by accepting any string as argument of the Invalid_argument constructor rather than just "index out of bounds".
2017-08-17 02:10:30 -07:00
let find_last_opt_result = M.find_last_opt (fun k -> k <= x) s1 in
if p = None && M.is_empty l then
Do not disable warnings by default when compiling tests (#1293) Before this comit, the tests using Makefile.several were compiled with all the compiler warnings turned off. This commit gets rid of this behaviour. Doing so revealed a number of warnings which are listed below. Directory testsuite/tests/basic: File "eval_order_5.ml", line 3, characters 16-22: Warning 5: this function application is partial, maybe some arguments are missing. Here the warning can't be avoided so the code has been modified to disable just this specific warning, locally. File "pr6322.ml", line 10, characters 2-15: Warning 3: deprecated: String.set Code updated to not use this operator any more. Directory testsuite/tests/basic-float: File "tfloat_record.ml", line 35, characters 8-53: Warning 55: Cannot inline: Function information unavailable Since the inline attribute cannot be applied and since this does not seem to be relevant for the test, this commit fixes the warning by getting rid of the attribute itself. Directory tests/basic-more: File morematch.ml has several warnings that are expected and have been ignored locally. File "sequential_and_or.ml", line 21, characters 2-17: Warning 3: deprecated: String.set Use Bytes.set instead. Done. The use of String.set was not relevant for the test. File "tformat.ml", line 15, characters 2-16: Warning 3: deprecated: Format.bprintf Given that the function is deprecated, the corresponding test has simply been removed. Directory tests/lib-bigarray: File "pr5115.ml", line 11, characters 2-11: Warning 10: this expression should have type unit. Given that the warning seems legitimate, add a call to ignore. Directory tests/lib-buffer: File "test.ml", line 42, characters 21-38: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) File "test.ml", line 52, characters 21-38: [same warning] File "test.ml", line 66, characters 21-38: [same warning] This warnign has been fixed by making the code able to handle any string used as argument of the Invalid_argument constructor. Directory tests/lib-set: File "testmap.ml", line 125, characters 10-21: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: None File "testmap.ml", line 151, characters 10-21: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: None These warnings were legitimate. One case was not taken into account. The code has been fixed. File "testset.ml", line 137, characters 10-16: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: None File "testset.ml", line 165, characters 10-16: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: None Same remark here. In directory tests/lib-stack: File "test.ml", line 110, characters 27-29: Warning 26: unused variable s2. Legitimate warning. Code fixed. In directory tests/lib-str: File "t01.ml", line 1068, characters 26-45: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) Legitimate warning. Code fixed. Directory tests/lib-threads: File "backtrace_threads.ml", line 7, characters 7-40: Warning 21: this statement never returns (or has an unsound type.) Legitimate warning. Code fixed. File "close.ml", line 10, characters 12-25: Warning 3: deprecated: String.create Use Bytes.create instead. Legitimate warning. Code fixed. File "fileio.ml", line 22, characters 15-28: Warning 3: deprecated: String.create Use Bytes.create instead. File "fileio.ml", line 36, characters 15-28: Warning 3: deprecated: String.create Use Bytes.create instead. Warnings legitimate. Code fixed. Directory tests/match-exception: File "match_failure.ml", line 9, characters 12-199: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: Some _ (However, some guarded clause may match this value.) This code must produce this warning so make sure it is locally ignored. Directory tests/misc: File "ephetest3.ml", line 99, characters 19-31: Warning 3: deprecated: Array.create Use Array.make instead. Legitimate warning. Code fixed. File "sorts.ml", line 131, characters 10-23: Warning 3: deprecated: String.create Use Bytes.create instead. Legitimate warning. Code fixed. File "sorts.ml", line 133, characters 4-38: Warning 3: deprecated: String.set Use Bytes.set instead. Legitimate warning. Code fixed. File "sorts.ml", line 4237, characters 15-24: Warning 3: deprecated: Sort.list Use List.sort instead. Test removed. File "sorts.ml", line 4373, characters 10-23: Warning 3: deprecated: String.create Use Bytes.create instead. Legitimate warning. Code fixed. File "sorts.ml", line 4408, characters 34-44: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4408, characters 45-55: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4431, characters 22-32: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4432, characters 22-32: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4433, characters 22-32: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4450, characters 21-31: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. Directory tests/misc-unsafe: File "almabench.ml", line 239, characters 20-22: Warning 3: deprecated: Pervasives.or Use (||) instead. Legitimate warning. Code fixed. File "soli.ml", line 38, characters 12-24: Warning 3: deprecated: Array.create Use Array.make instead. Legitimate warning. Code fixed. Directory tests/prim-bigstring: File "bigstring_access.ml", line 34, characters 23-46: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) File "bigstring_access.ml", line 41, characters 23-46: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) File "string_access.ml", line 21, characters 23-46: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) File "string_access.ml", line 28, characters 23-46: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) Legitimate warnings. Fixed by accepting any string as argument of the Invalid_argument constructor rather than just "index out of bounds".
2017-08-17 02:10:30 -07:00
match find_last_opt_result with
None -> true
| _ -> false
else
Do not disable warnings by default when compiling tests (#1293) Before this comit, the tests using Makefile.several were compiled with all the compiler warnings turned off. This commit gets rid of this behaviour. Doing so revealed a number of warnings which are listed below. Directory testsuite/tests/basic: File "eval_order_5.ml", line 3, characters 16-22: Warning 5: this function application is partial, maybe some arguments are missing. Here the warning can't be avoided so the code has been modified to disable just this specific warning, locally. File "pr6322.ml", line 10, characters 2-15: Warning 3: deprecated: String.set Code updated to not use this operator any more. Directory testsuite/tests/basic-float: File "tfloat_record.ml", line 35, characters 8-53: Warning 55: Cannot inline: Function information unavailable Since the inline attribute cannot be applied and since this does not seem to be relevant for the test, this commit fixes the warning by getting rid of the attribute itself. Directory tests/basic-more: File morematch.ml has several warnings that are expected and have been ignored locally. File "sequential_and_or.ml", line 21, characters 2-17: Warning 3: deprecated: String.set Use Bytes.set instead. Done. The use of String.set was not relevant for the test. File "tformat.ml", line 15, characters 2-16: Warning 3: deprecated: Format.bprintf Given that the function is deprecated, the corresponding test has simply been removed. Directory tests/lib-bigarray: File "pr5115.ml", line 11, characters 2-11: Warning 10: this expression should have type unit. Given that the warning seems legitimate, add a call to ignore. Directory tests/lib-buffer: File "test.ml", line 42, characters 21-38: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) File "test.ml", line 52, characters 21-38: [same warning] File "test.ml", line 66, characters 21-38: [same warning] This warnign has been fixed by making the code able to handle any string used as argument of the Invalid_argument constructor. Directory tests/lib-set: File "testmap.ml", line 125, characters 10-21: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: None File "testmap.ml", line 151, characters 10-21: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: None These warnings were legitimate. One case was not taken into account. The code has been fixed. File "testset.ml", line 137, characters 10-16: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: None File "testset.ml", line 165, characters 10-16: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: None Same remark here. In directory tests/lib-stack: File "test.ml", line 110, characters 27-29: Warning 26: unused variable s2. Legitimate warning. Code fixed. In directory tests/lib-str: File "t01.ml", line 1068, characters 26-45: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) Legitimate warning. Code fixed. Directory tests/lib-threads: File "backtrace_threads.ml", line 7, characters 7-40: Warning 21: this statement never returns (or has an unsound type.) Legitimate warning. Code fixed. File "close.ml", line 10, characters 12-25: Warning 3: deprecated: String.create Use Bytes.create instead. Legitimate warning. Code fixed. File "fileio.ml", line 22, characters 15-28: Warning 3: deprecated: String.create Use Bytes.create instead. File "fileio.ml", line 36, characters 15-28: Warning 3: deprecated: String.create Use Bytes.create instead. Warnings legitimate. Code fixed. Directory tests/match-exception: File "match_failure.ml", line 9, characters 12-199: Warning 8: this pattern-matching is not exhaustive. Here is an example of a case that is not matched: Some _ (However, some guarded clause may match this value.) This code must produce this warning so make sure it is locally ignored. Directory tests/misc: File "ephetest3.ml", line 99, characters 19-31: Warning 3: deprecated: Array.create Use Array.make instead. Legitimate warning. Code fixed. File "sorts.ml", line 131, characters 10-23: Warning 3: deprecated: String.create Use Bytes.create instead. Legitimate warning. Code fixed. File "sorts.ml", line 133, characters 4-38: Warning 3: deprecated: String.set Use Bytes.set instead. Legitimate warning. Code fixed. File "sorts.ml", line 4237, characters 15-24: Warning 3: deprecated: Sort.list Use List.sort instead. Test removed. File "sorts.ml", line 4373, characters 10-23: Warning 3: deprecated: String.create Use Bytes.create instead. Legitimate warning. Code fixed. File "sorts.ml", line 4408, characters 34-44: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4408, characters 45-55: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4431, characters 22-32: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4432, characters 22-32: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4433, characters 22-32: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. File "sorts.ml", line 4450, characters 21-31: Warning 3: deprecated: Sort.array Use Array.sort instead. Test removed. Directory tests/misc-unsafe: File "almabench.ml", line 239, characters 20-22: Warning 3: deprecated: Pervasives.or Use (||) instead. Legitimate warning. Code fixed. File "soli.ml", line 38, characters 12-24: Warning 3: deprecated: Array.create Use Array.make instead. Legitimate warning. Code fixed. Directory tests/prim-bigstring: File "bigstring_access.ml", line 34, characters 23-46: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) File "bigstring_access.ml", line 41, characters 23-46: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) File "string_access.ml", line 21, characters 23-46: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) File "string_access.ml", line 28, characters 23-46: Warning 52: Code should not depend on the actual values of this constructor's arguments. They are only for information and may change in future versions. (See manual section 8.5) Legitimate warnings. Fixed by accepting any string as argument of the Invalid_argument constructor rather than just "index out of bounds".
2017-08-17 02:10:30 -07:00
(match find_last_opt_result with
| None -> false
| Some (k, v) ->
(match p with
| None -> (k, v) = M.max_binding l
| Some v1 -> (k, v) = (x, v1))));
check "split"
(let (l, p, r) = M.split x s1 in
fun i ->
if i < x then img i l = img i s1
else if i > x then img i r = img i s1
else p = img i s1);
checkbool "to_seq_of_seq"
(M.equal (=) s1 (M.of_seq @@ M.to_seq s1));
checkbool "to_seq_from"
(let seq = M.to_seq_from x s1 in
let ok1 = List.of_seq seq |> List.for_all (fun (y,_) -> y >= x) in
let ok2 =
(M.to_seq s1 |> List.of_seq |> List.filter (fun (y,_) -> y >= x))
=
(List.of_seq seq)
in
ok1 && ok2);
()
let rkey() = Random.int 10
let rdata() = Random.float 1.0
let rmap() =
let s = ref M.empty in
for i = 1 to Random.int 10 do s := M.add (rkey()) (rdata()) !s done;
!s
let _ =
Random.init 42;
for i = 1 to 10000 do test (rkey()) (rdata()) (rmap()) (rmap()) done
let () =
(* check that removing a binding from a map that is not present in this map
(1) doesn't allocate and (2) return the original map *)
let m1 = ref M.empty in
for i = 1 to 10 do m1 := M.add i (float i) !m1 done;
let m2 = ref !m1 in
let a0 = Gc.allocated_bytes () in
let a1 = Gc.allocated_bytes () in
for i = 11 to 30 do m2 := M.remove i !m2 done;
let a2 = Gc.allocated_bytes () in
assert (!m2 == !m1);
assert(a2 -. a1 = a1 -. a0)
let () =
(* check that filtering a map where all bindings are satisfied by
the given predicate returns the original map *)
let m1 = ref M.empty in
for i = 1 to 10 do m1 := M.add i (float i) !m1 done;
let m2 = M.filter (fun e _ -> e >= 0) !m1 in
assert (m2 == !m1)
let () =
(* check that adding a binding "x -> y" to a map that already
contains it doesn't allocate and return the original map. *)
let m1 = ref M.empty in
let tmp = ref None in
for i = 1 to 10 do
tmp := Some (float i);
m1 := M.add i !tmp !m1
done;
let m2 = ref !m1 in
let a0 = Gc.allocated_bytes () in
let a1 = Gc.allocated_bytes () in
(* 10 |-> !tmp is already present in !m2 *)
m2 := M.add 10 !tmp !m2;
let a2 = Gc.allocated_bytes () in
assert (!m2 == !m1);
assert(a2 -. a1 = a1 -. a0);
(* 4 |-> Some 84. is not present in !m2 *)
m2 := M.add 4 (Some 84.) !m2;
assert (not (!m2 == !m1));