diff --git a/CHANGELOG.md b/CHANGELOG.md index 905347d6f..ee7fe8873 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -1,6 +1,11 @@ # Changelog ## main +- breaking: CCListLabel.compare and CCListLabel.equal takes the function on the elements as named arguments +- breaking: CCListLabel.init now takes the length as a named arguments to follow the Stdlib +- breaking: invert the argument of CCFun.compose to align it with the Stdlib +- breaking: change the semantic of CCFloat.{min,max} with respect to NaN to follow the Stdlib +- breaking: change the semantic of CCInt.rem with respect to negative number to follow the Stdlib ## 3.15 @@ -38,6 +43,7 @@ ## 3.13 +- breaking: bump minimum version of OCaml to 4.08 - breaking: delete containers-thread (which was deprecated) - breaking: pp: modify `Ext.t` so it takes surrounding value - breaking: remove CCShims diff --git a/src/core/CCArray.ml b/src/core/CCArray.ml index 00c57142d..85d498fd0 100644 --- a/src/core/CCArray.ml +++ b/src/core/CCArray.ml @@ -455,15 +455,6 @@ let pp_i ?(pp_start = fun _ () -> ()) ?(pp_stop = fun _ () -> ()) let to_string ?(sep = ", ") item_to_string a = Array.to_list a |> List.map item_to_string |> String.concat sep -let to_seq a = - let rec aux i () = - if i >= length a then - Seq.Nil - else - Seq.Cons (a.(i), aux (i + 1)) - in - aux 0 - let to_iter a k = iter k a let to_gen a = diff --git a/src/core/CCArray.mli b/src/core/CCArray.mli index d19d42523..8d9c14e52 100644 --- a/src/core/CCArray.mli +++ b/src/core/CCArray.mli @@ -240,14 +240,6 @@ val to_iter : 'a t -> 'a iter in modification of the iterator. @since 2.8 *) -val to_seq : 'a t -> 'a Seq.t -(** [to_seq a] returns a [Seq.t] of the elements of an array [a]. - The input array [a] is shared with the sequence and modification of it will result - in modification of the sequence. - Renamed from [to_std_seq] since 3.0. - @since 3.0 -*) - val to_gen : 'a t -> 'a gen (** [to_gen a] returns a [gen] of the elements of an array [a]. *) diff --git a/src/core/CCArrayLabels.mli b/src/core/CCArrayLabels.mli index 8663c7ddd..2a1f705f6 100644 --- a/src/core/CCArrayLabels.mli +++ b/src/core/CCArrayLabels.mli @@ -219,13 +219,6 @@ val fold2 : f:('acc -> 'a -> 'b -> 'acc) -> init:'acc -> 'a t -> 'b t -> 'acc @raise Invalid_argument if [a] and [b] have distinct lengths. @since 0.20 *) -val iter2 : f:('a -> 'b -> unit) -> 'a t -> 'b t -> unit -(** [iter2 ~f a b] iterates on the two arrays [a] and [b] stepwise. - It is equivalent to [f a0 b0; …; f a.(length a - 1) b.(length b - 1); ()]. - - @raise Invalid_argument if [a] and [b] have distinct lengths. - @since 0.20 *) - val shuffle : 'a t -> unit (** [shuffle a] randomly shuffles the array [a], in place. *) @@ -248,14 +241,6 @@ val to_iter : 'a t -> 'a iter in modification of the iterator. @since 2.8 *) -val to_seq : 'a t -> 'a Seq.t -(** [to_seq a] returns a [Seq.t] of the elements of an array [a]. - The input array [a] is shared with the sequence and modification of it will result - in modification of the sequence. - Renamed from [to_std_seq] since 3.0. - @since 3.0 -*) - val to_gen : 'a t -> 'a gen (** [to_gen a] returns a [gen] of the elements of an array [a]. *) @@ -286,14 +271,6 @@ val pp_i : By defaults [pp_start] and [pp_stop] does nothing and [pp_sep] defaults to (fun out -> Format.fprintf out ",@ "). *) -val map2 : f:('a -> 'b -> 'c) -> 'a t -> 'b t -> 'c t -(** [map2 ~f a b] applies function [f] to all elements of [a] and [b], - and builds an array with the results returned by [f]: - [[| f a.(0) b.(0); …; f a.(length a - 1) b.(length b - 1)|]]. - - @raise Invalid_argument if [a] and [b] have distinct lengths. - @since 0.20 *) - val rev : 'a t -> 'a t (** [rev a] copies the array [a] and reverses it in place. @since 0.20 *) @@ -308,7 +285,7 @@ val filter_map : f:('a -> 'b option) -> 'a t -> 'b t element of [a] is discarded. *) val monoid_product : f:('a -> 'b -> 'c) -> 'a t -> 'b t -> 'c t -(** [monoid_product ~f a b] passes all combinaisons of tuples from the two arrays [a] and [b] +(** [monoid_product ~f a b] passes all combinaisons of tuples from the two arrays [a] and [b] to the function [f]. @since 2.8 *) diff --git a/src/core/CCBool.ml b/src/core/CCBool.ml index b7e97bb55..ab35f3626 100644 --- a/src/core/CCBool.ml +++ b/src/core/CCBool.ml @@ -1,9 +1,6 @@ (* This file is free software, part of containers. See file "license" for more details. *) -type t = bool - -let equal (a : bool) b = Stdlib.( = ) a b -let compare (a : bool) b = Stdlib.compare a b +include Bool let if_then f x = if x then @@ -17,12 +14,6 @@ let if_then_else f g x = else g () -let to_int (x : bool) : int = - if x then - 1 - else - 0 - let of_int x : t = x <> 0 type 'a printer = Format.formatter -> 'a -> unit diff --git a/src/core/CCBool.mli b/src/core/CCBool.mli index 0ac4c40c0..81a7c3462 100644 --- a/src/core/CCBool.mli +++ b/src/core/CCBool.mli @@ -2,13 +2,8 @@ (** Basic Bool functions *) -type t = bool - -val compare : t -> t -> int -(** [compare b1 b2] is the total ordering on booleans [b1] and [b2], similar to {!Stdlib.compare}. *) - -val equal : t -> t -> bool -(** [equal b1 b2] is [true] if [b1] and [b2] are the same. *) +include module type of Bool +(** @inline *) val if_then : (unit -> 'a) -> t -> 'a option (** [if_then f x] is [Some (f ())] if [x] is true and None otherwise. @@ -18,10 +13,6 @@ val if_then_else : (unit -> 'a) -> (unit -> 'a) -> t -> 'a (** [if_then_else f g x] is [f ()] if [x] is true and [g ()] otherwise. @since 3.13 *) -val to_int : t -> int -(** [to_int true = 1], [to_int false = 0]. - @since 2.7 *) - val of_int : int -> t (** [of_int i] is the same as [i <> 0] @since 2.7 *) diff --git a/src/core/CCChar.mli b/src/core/CCChar.mli index d18eb48ed..06a80c3da 100644 --- a/src/core/CCChar.mli +++ b/src/core/CCChar.mli @@ -9,12 +9,6 @@ include module type of struct include Char end -val compare : t -> t -> int -(** The comparison function for characters, with the same specification as - {!Stdlib.compare}. Along with the type [t], this function [compare] - allows the module [Char] to be passed as argument to the functors - {!Set.Make} and {!Map.Make}. *) - val of_int_exn : int -> t (** Alias to {!Char.chr}. Return the character with the given ASCII code. diff --git a/src/core/CCEither.ml b/src/core/CCEither.ml index 30a64f6ff..10832602a 100644 --- a/src/core/CCEither.ml +++ b/src/core/CCEither.ml @@ -5,6 +5,12 @@ type 'a equal = 'a -> 'a -> bool type 'a ord = 'a -> 'a -> int type 'a printer = Format.formatter -> 'a -> unit +[@@@ifge 4.12] + +include Either + +[@@@else_] + (** {2 Basics} *) type ('a, 'b) t = ('a, 'b) Either.t = @@ -62,6 +68,8 @@ let compare ~left ~right e1 e2 = | Left l1, Left l2 -> left l1 l2 | Right r1, Right r2 -> right r1 r2 +[@@@endif] + (** {2 IO} *) let pp ~left ~right fmt = function diff --git a/src/core/CCEither.mli b/src/core/CCEither.mli index ce6f4e18d..31817b295 100644 --- a/src/core/CCEither.mli +++ b/src/core/CCEither.mli @@ -13,6 +13,13 @@ type 'a equal = 'a -> 'a -> bool type 'a ord = 'a -> 'a -> int type 'a printer = Format.formatter -> 'a -> unit +[@@@ifge 4.12] + +include module type of Either +(** @inline *) + +[@@@else_] + (** {2 Basics} *) type ('a, 'b) t = ('a, 'b) Either.t = @@ -70,6 +77,8 @@ val compare : ('a, 'b) t -> int +[@@@endif] + (** {2 IO} *) val pp : left:'a printer -> right:'b printer -> ('a, 'b) t printer diff --git a/src/core/CCFloat.ml b/src/core/CCFloat.ml index 7b62f8329..72c241bbe 100644 --- a/src/core/CCFloat.ml +++ b/src/core/CCFloat.ml @@ -1,13 +1,6 @@ (* This file is free software, part of containers. See file "license" for more details. *) -type t = float - -type fpclass = Stdlib.fpclass = - | FP_normal - | FP_subnormal - | FP_zero - | FP_infinite - | FP_nan +include Float module Infix = struct let ( = ) : t -> t -> bool = Stdlib.( = ) @@ -27,47 +20,11 @@ include Infix [@@@ocaml.warning "-32"] -let nan = Stdlib.nan -let infinity = Stdlib.infinity -let neg_infinity = Stdlib.neg_infinity let max_value = infinity let min_value = neg_infinity let max_finite_value = Stdlib.max_float -let epsilon = Stdlib.epsilon_float -let pi = 0x1.921fb54442d18p+1 -let is_nan x = Stdlib.(classify_float x = Stdlib.FP_nan) -let add = ( +. ) -let sub = ( -. ) -let mul = ( *. ) -let div = ( /. ) -let neg = ( ~-. ) -let abs = Stdlib.abs_float let scale = ( *. ) -let min (x : t) y = - match Stdlib.classify_float x, Stdlib.classify_float y with - | FP_nan, _ -> y - | _, FP_nan -> x - | _ -> - if x < y then - x - else - y - -let max (x : t) y = - match Stdlib.classify_float x, Stdlib.classify_float y with - | FP_nan, _ -> y - | _, FP_nan -> x - | _ -> - if x > y then - x - else - y - -let equal (a : float) b = a = b -let hash : t -> int = Hashtbl.hash -let compare (a : float) b = Stdlib.compare a b - [@@@ocaml.warning "+32"] type 'a printer = Format.formatter -> 'a -> unit @@ -91,22 +48,7 @@ let sign_exn (a : float) = else compare a 0. -let round x = - let low = floor x in - let high = ceil x in - if x -. low > high -. x then - high - else - low - -let to_int (a : float) = Stdlib.int_of_float a -let of_int (a : int) = Stdlib.float_of_int a -let to_string (a : float) = Stdlib.string_of_float a let of_string_exn (a : string) = Stdlib.float_of_string a - -let of_string_opt (a : string) = - try Some (Stdlib.float_of_string a) with Failure _ -> None - let random n st = Random.State.float st n let random_small = random 100.0 let random_range i j st = i +. random (j -. i) st diff --git a/src/core/CCFloat.mli b/src/core/CCFloat.mli index 527091948..ee97e6d3f 100644 --- a/src/core/CCFloat.mli +++ b/src/core/CCFloat.mli @@ -3,17 +3,8 @@ (** Basic operations on floating-point numbers @since 0.6.1 *) -type t = float - -type fpclass = Stdlib.fpclass = - | FP_normal - | FP_subnormal - | FP_zero - | FP_infinite - | FP_nan - -val nan : t -(** [nan] is Not a Number (NaN). Equal to {!Stdlib.nan}. *) +include module type of Float +(** @inline *) val max_value : t (** [max_value] is Positive infinity. Equal to {!Stdlib.infinity}. *) @@ -24,50 +15,13 @@ val min_value : t val max_finite_value : t (** [max_finite_value] is the largest finite float value. Equal to {!Stdlib.max_float}. *) -val epsilon : t -(** [epsilon] is the smallest positive float x such that [1.0 +. x <> 1.0]. - Equal to {!Stdlib.epsilon_float}. *) - -val pi : t -(** [pi] is the constant pi. The ratio of a circumference to its diameter. - @since 3.0 *) - -val is_nan : t -> bool -(** [is_nan f] returns [true] if f is NaN, [false] otherwise. *) - -val add : t -> t -> t -(** [add x y] is equal to [x +. y]. *) - -val sub : t -> t -> t -(** [sub x y] is equal to [x -. y]. *) - -val neg : t -> t -(** [neg x] is equal to [~-. x]. *) - -val abs : t -> t -(** [abs x] is the absolute value of the floating-point number [x]. - Equal to {!Stdlib.abs_float}. *) - val scale : t -> t -> t (** [scale x y] is equal to [x *. y]. *) -val min : t -> t -> t -(** [min x y] returns the min of the two given values [x] and [y]. *) - -val max : t -> t -> t -(** [max x y] returns the max of the two given values [x] and [y]. *) - -val equal : t -> t -> bool -(** [equal x y] is [true] if [x] and [y] are the same. *) - -val compare : t -> t -> int -(** [compare x y] is {!Stdlib.compare x y}. *) - type 'a printer = Format.formatter -> 'a -> unit type 'a random_gen = Random.State.t -> 'a val pp : t printer -val hash : t -> int val random : t -> t random_gen val random_small : t random_gen val random_range : t -> t -> t random_gen @@ -76,11 +30,6 @@ val fsign : t -> t (** [fsign x] is one of [-1., -0., +0., +1.], or [nan] if [x] is NaN. @since 0.7 *) -val round : t -> t -(** [round x] returns the closest integer value, either above or below. - For [n + 0.5], [round] returns [n]. - @since 0.20 *) - exception TrapNaN of string val sign_exn : t -> int @@ -89,23 +38,11 @@ val sign_exn : t -> int Note that infinities have defined signs in OCaml. @since 0.7 *) -val to_int : t -> int -(** Alias to {!int_of_float}. - Unspecified if outside of the range of integers. *) - -val of_int : int -> t -(** Alias to {!float_of_int}. *) - -val to_string : t -> string - val of_string_exn : string -> t (** Alias to {!float_of_string}. @raise Failure in case of failure. @since 1.2 *) -val of_string_opt : string -> t option -(** @since 3.0 *) - val equal_precision : epsilon:t -> t -> t -> bool (** Equality with allowed error up to a non negative epsilon value. *) diff --git a/src/core/CCFormat.ml b/src/core/CCFormat.ml index ef1c9ca12..9dd8037c7 100644 --- a/src/core/CCFormat.ml +++ b/src/core/CCFormat.ml @@ -31,6 +31,9 @@ let break fmt (m, n) = Format.pp_print_break fmt m n let newline = Format.pp_force_newline let substring out (s, i, len) : unit = string out (String.sub s i len) let text = Format.pp_print_text +let option = Format.pp_print_option +let opt = option +let result = Format.pp_print_result let string_lines out (s : string) : unit = fprintf out "@["; @@ -88,11 +91,6 @@ let iter ?(sep = return ",@ ") pp fmt seq = sep fmt (); pp fmt x) -let opt pp fmt x = - match x with - | None -> Format.pp_print_string fmt "none" - | Some x -> Format.fprintf fmt "some %a" pp x - let pair ?(sep = return ",@ ") ppa ppb fmt (a, b) = Format.fprintf fmt "%a%a%a" ppa a sep () ppb b diff --git a/src/core/CCFormat.mli b/src/core/CCFormat.mli index 4426f662c..12b1ca815 100644 --- a/src/core/CCFormat.mli +++ b/src/core/CCFormat.mli @@ -99,10 +99,16 @@ val arrayi : ?sep:unit printer -> (int * 'a) printer -> 'a array printer val seq : ?sep:unit printer -> 'a printer -> 'a Seq.t printer val iter : ?sep:unit printer -> 'a printer -> 'a iter printer -val opt : 'a printer -> 'a option printer -(** [opt pp] prints options as follows: - - [Some x] will become "some foo" if [pp x ---> "foo"]. - - [None] will become "none". *) +val option : ?none:unit printer -> 'a printer -> 'a option printer +(** [opt ?none pp] prints options as follows: + - [Some x] will become [pp x] + - [None] will become [none ()] + @since NEXT_RELEASE *) + +val opt : ?none:unit printer -> 'a printer -> 'a option printer +(** Alias of {!option} *) + +val result : ok:'a printer -> error:'e printer -> ('a, 'e) result printer (** In the tuple printers, the [sep] argument is only available. @since 0.17 *) diff --git a/src/core/CCFun.ml b/src/core/CCFun.ml index abb2a6a26..7605d7668 100644 --- a/src/core/CCFun.ml +++ b/src/core/CCFun.ml @@ -10,7 +10,13 @@ include Fun let[@inline] and_pred f g x = f x && g x let[@inline] or_pred f g x = f x || g x -let[@inline] compose f g x = g (f x) + +[@@@iflt 5.2] + +let[@inline] compose f g x = f (g x) + +[@@@endif] + let[@inline] compose_binop f g x y = g (f x) (f y) let[@inline] curry f x y = f (x, y) let[@inline] uncurry f (x, y) = f x y @@ -63,7 +69,7 @@ let rec iterate n f x = module Infix = struct (* default implem for some operators *) - let ( %> ) = compose + let ( %> ) f g = compose g f let[@inline] ( % ) f g x = f (g x) let ( let@ ) = ( @@ ) let ( ||> ) (a, b) f = f a b diff --git a/src/core/CCFun.mli b/src/core/CCFun.mli index 882611012..d5d33c74c 100644 --- a/src/core/CCFun.mli +++ b/src/core/CCFun.mli @@ -17,8 +17,13 @@ val or_pred : ('a -> bool) -> ('a -> bool) -> 'a -> bool @since 3.13.1 *) -val compose : ('a -> 'b) -> ('b -> 'c) -> 'a -> 'c -(** [compose f g x] is [g (f x)]. Composition. *) +[@@@iflt 5.2] + +val compose : ('b -> 'c) -> ('a -> 'b) -> 'a -> 'c +(** [compose f g x] is [f (g x)]. Composition. + @since NEXT_RELEASE arguments are inversted *) + +[@@@endif] val compose_binop : ('a -> 'b) -> ('b -> 'b -> 'c) -> 'a -> 'a -> 'c (** [compose_binop f g] is [fun x y -> g (f x) (f y)]. @@ -84,7 +89,8 @@ val iterate : int -> ('a -> 'a) -> 'a -> 'a module Infix : sig val ( %> ) : ('a -> 'b) -> ('b -> 'c) -> 'a -> 'c - (** [(f %> g) x] or [(%>) f g x] is [g (f x)]. Alias to [compose]. *) + (** [(f %> g) x] or [(%>) f g x] is [g (f x)]. Infix version of [compose]. + The order of the arguments of [%>] and {!compose} are inverted. *) val ( % ) : ('b -> 'c) -> ('a -> 'b) -> 'a -> 'c (** [(f % g) x] or [(%) f g x] is [f (g x)]. Mathematical composition. *) diff --git a/src/core/CCHashtbl.ml b/src/core/CCHashtbl.ml index 9406cbe30..6356d15eb 100644 --- a/src/core/CCHashtbl.ml +++ b/src/core/CCHashtbl.ml @@ -189,11 +189,6 @@ module type S = sig using [f] in an unspecified order. @since 3.3 *) - val add_seq : 'a t -> (key * 'a) Seq.t -> unit - (** Add the corresponding pairs to the table, using {!Hashtbl.add}. - Renamed from [add_std_seq] since 3.0. - @since 3.0 *) - val add_seq_with : f:(key -> 'a -> 'a -> 'a) -> 'a t -> (key * 'a) Seq.t -> unit (** Add the corresponding pairs to the table, using {!Hashtbl.add}. @@ -211,11 +206,6 @@ module type S = sig using [f] in an unspecified order. @since 3.3 *) - val of_seq : (key * 'a) Seq.t -> 'a t - (** From the given bindings, added in order. - Renamed from [of_std_seq] since 3.0. - @since 3.0 *) - val of_seq_with : f:(key -> 'a -> 'a -> 'a) -> (key * 'a) Seq.t -> 'a t (** From the given bindings, added in order. If a key occurs multiple times in the input, the values are combined @@ -349,8 +339,6 @@ module Make (X : Hashtbl.HashedType) : | exception Not_found -> add tbl k v | v2 -> replace tbl k (f k v v2)) - let add_seq tbl seq = Seq.iter (fun (k, v) -> add tbl k v) seq - let add_seq_with ~f tbl seq = Seq.iter (fun (k, v) -> @@ -366,7 +354,6 @@ module Make (X : Hashtbl.HashedType) : tbl let of_iter i = mk_tbl_ add_iter i - let of_seq i = mk_tbl_ add_seq i let of_iter_with ~f i = mk_tbl_ (add_iter_with ~f) i let of_seq_with ~f i = mk_tbl_ (add_seq_with ~f) i let add_iter_count tbl i = i (fun k -> incr tbl k) diff --git a/src/core/CCHashtbl.mli b/src/core/CCHashtbl.mli index d01de1340..c5445a677 100644 --- a/src/core/CCHashtbl.mli +++ b/src/core/CCHashtbl.mli @@ -253,11 +253,6 @@ module type S = sig using [f] in an unspecified order. @since 3.3 *) - val add_seq : 'a t -> (key * 'a) Seq.t -> unit - (** Add the corresponding pairs to the table, using {!Hashtbl.add}. - Renamed from [add_std_seq] since 3.0. - @since 3.0 *) - val add_seq_with : f:(key -> 'a -> 'a -> 'a) -> 'a t -> (key * 'a) Seq.t -> unit (** Add the corresponding pairs to the table, using {!Hashtbl.add}. @@ -275,11 +270,6 @@ module type S = sig using [f] in an unspecified order. @since 3.3 *) - val of_seq : (key * 'a) Seq.t -> 'a t - (** From the given bindings, added in order. - Renamed from [of_std_seq] since 3.0. - @since 3.0 *) - val of_seq_with : f:(key -> 'a -> 'a -> 'a) -> (key * 'a) Seq.t -> 'a t (** From the given bindings, added in order. If a key occurs multiple times in the input, the values are combined diff --git a/src/core/CCInt.ml b/src/core/CCInt.ml index a2efe7bc6..801b08578 100644 --- a/src/core/CCInt.ml +++ b/src/core/CCInt.ml @@ -2,24 +2,8 @@ include Int -type t = int type 'a iter = ('a -> unit) -> unit -let zero = 0 -let one = 1 -let minus_one = -1 -let add = ( + ) -let sub = ( - ) -let mul = ( * ) -let div = ( / ) -let succ = succ -let pred = pred -let abs = abs -let max_int = max_int -let min_int = min_int -let equal (a : int) b = Stdlib.( = ) a b -let compare (a : int) b = compare a b - (* use FNV: https://en.wikipedia.org/wiki/Fowler%E2%80%93Noll%E2%80%93Vo_hash_function *) let hash (n : int) : int = @@ -65,7 +49,6 @@ let range' i j yield = range i (j + 1) yield let sign i = compare i 0 -let neg i = -i let pow a b = let rec aux acc = function @@ -119,9 +102,13 @@ end include Infix +[@@@iflt 4.13] + let min : t -> t -> t = Stdlib.min let max : t -> t -> t = Stdlib.max +[@@@endif] + let floor_div a n = if a < 0 && n >= 0 then ((a + 1) / n) - 1 @@ -147,11 +134,8 @@ let random_small = random 100 let random_range i j st = i + random (j - i) st let pp fmt = Format.pp_print_int fmt let most_significant_bit = -1 lxor (-1 lsr 1) -let to_string = string_of_int let of_string s = try Some (int_of_string s) with Failure _ -> None let of_string_exn = Stdlib.int_of_string -let to_float = float_of_int -let of_float = int_of_float type output = char -> unit @@ -248,11 +232,3 @@ let popcount (b : int) : int = let b = add b (shift_right_logical b 32) in let b = logand b 0x7fL in to_int b - -let logand = ( land ) -let logor = ( lor ) -let logxor = ( lxor ) -let lognot = lnot -let shift_left = ( lsl ) -let shift_right = ( asr ) -let shift_right_logical = ( lsr ) diff --git a/src/core/CCInt.mli b/src/core/CCInt.mli index 65b01ef18..525d8bf00 100644 --- a/src/core/CCInt.mli +++ b/src/core/CCInt.mli @@ -5,65 +5,6 @@ include module type of Int (** @inline *) -type t = int - -val zero : t -(** [zero] is the integer [0]. - @since 3.0 *) - -val one : t -(** [one] is the integer [1]. - @since 3.0 *) - -val minus_one : t -(** [minus_one] is the integer [-1]. - @since 3.0 *) - -val add : t -> t -> t -(** [add x y] is [x + y]. - @since 3.0 *) - -val sub : t -> t -> t -(** [sub x y] is [x - y]. - @since 3.0 *) - -val mul : t -> t -> t -(** [mul x y] is [x * y]. - @since 3.0 *) - -val div : t -> t -> t -(** [div x y] is [x / y] - @since 3.0 *) - -val succ : t -> t -(** [succ x] is [x + 1]. - @since 3.0 *) - -val pred : t -> t -(** [pred x] is [x - 1]. - @since 3.0 *) - -val abs : t -> t -(** [abs x] is the absolute value of [x]. It is [x] if [x] is positive - and [neg x] otherwise. - @since 3.0 *) - -val max_int : t -(** [max_int] is the maximum integer. - @since 3.0 *) - -val min_int : t -(** [min_int] is the minimum integer. - @since 3.0 *) - -val compare : t -> t -> int -(** [compare x y] is the comparison function for integers - with the same specification as {!Stdlib.compare}. *) - -val equal : t -> t -> bool -(** [equal x y] is [true] iff [x] and [y] are equal. - Equality function for integers. *) - val hash : t -> int (** [hash x] computes the hash of [x]. *) @@ -71,11 +12,6 @@ val sign : t -> int (** [sign x] return [0] if [x = 0], [-1] if [x < 0] and [1] if [x > 0]. Same as [compare x 0].*) -val neg : t -> t -(** [neg x] is [- x]. - Unary negation. - @since 0.5 *) - val pow : t -> t -> t (** [pow base exponent] returns [base] raised to the power of [exponent]. [pow x y = x^y] for positive integers [x] and [y]. @@ -103,22 +39,6 @@ val random_range : int -> int -> t random_gen val pp : t printer (** [pp ppf x] prints the integer [x] on [ppf]. *) -val to_float : t -> float -(** [to_float] is the same as [float_of_int] - @since 3.0*) - -[@@@ocaml.warning "-32"] - -val of_float : float -> t -(** [to_float] is the same as [int_of_float] - @since 3.0*) - -[@@@ocaml.warning "+32"] - -val to_string : t -> string -(** [to_string x] returns the string representation of the integer [x], in signed decimal. - @since 0.13 *) - val of_string : string -> t option (** [of_string s] converts the given string [s] into an integer. Safe version of {!of_string_exn}. @@ -130,11 +50,6 @@ val of_string_exn : string -> t @raise Failure in case of failure. @since 3.0 *) -val of_float : float -> t -(** [of_float x] converts the given floating-point number [x] to an integer. - Alias to {!int_of_float}. - @since 3.0 *) - val pp_binary : t printer (** [pp_binary ppf x] prints [x] on [ppf]. Print as "0b00101010". @@ -144,6 +59,8 @@ val to_string_binary : t -> string (** [to_string_binary x] returns the string representation of the integer [x], in binary. @since 0.20 *) +[@@@iflt 4.13] + val min : t -> t -> t (** [min x y] returns the minimum of the two integers [x] and [y]. @since 0.17 *) @@ -152,6 +69,8 @@ val max : t -> t -> t (** [max x y] returns the maximum of the two integers [x] and [y]. @since 0.17 *) +[@@@endif] + val range_by : step:t -> t -> t -> t iter (** [range_by ~step i j] iterates on integers from [i] to [j] included, where the difference between successive elements is [step]. @@ -173,34 +92,6 @@ val popcount : t -> int (** Number of bits set to 1 @since 3.0 *) -val logand : t -> t -> t -(** [logand] is the same as [(land)]. - @since 3.0 *) - -val logor : t -> t -> t -(** [logand] is the same as [(lor)]. - @since 3.0 *) - -val logxor : t -> t -> t -(** [logxor] is the same as [(lxor)]. - @since 3.0 *) - -val lognot : t -> t -(** [logand] is the same as [lnot]. - @since 3.0 *) - -val shift_left : t -> int -> t -(** [shift_left] is the same as [(lsl)]. - @since 3.0 *) - -val shift_right : t -> int -> t -(** [shift_right] is the same as [(asr)]. - @since 3.0 *) - -val shift_right_logical : t -> int -> t -(** [shift_right_logical] is the same as [(lsr)]. - @since 3.0 *) - (** {2 Infix Operators} @since 0.17 *) diff --git a/src/core/CCInt32.ml b/src/core/CCInt32.ml index 42cbdf5cc..45b3f4a51 100644 --- a/src/core/CCInt32.ml +++ b/src/core/CCInt32.ml @@ -2,9 +2,18 @@ include Int32 +[@@@iflt 4.13] + let min : t -> t -> t = Stdlib.min let max : t -> t -> t = Stdlib.max + +[@@@endif] +[@@@iflt 5.1] + let hash x = Stdlib.abs (to_int x) + +[@@@endif] + let sign i = compare i zero let pow a b = @@ -110,7 +119,6 @@ let random_range i j st = add i (random (sub j i) st) let of_string_exn = of_string let of_string x = try Some (of_string_exn x) with Failure _ -> None -let of_string_opt = of_string let most_significant_bit = logxor (neg 1l) (shift_right_logical (neg 1l) 1) type output = char -> unit diff --git a/src/core/CCInt32.mli b/src/core/CCInt32.mli index 218168d7e..bd1940cde 100644 --- a/src/core/CCInt32.mli +++ b/src/core/CCInt32.mli @@ -18,6 +18,8 @@ include module type of struct include Int32 end +[@@@iflt 4.13] + val min : t -> t -> t (** [min x y] returns the minimum of the two integers [x] and [y]. @since 3.0 *) @@ -26,10 +28,15 @@ val max : t -> t -> t (** [max x y] returns the maximum of the two integers [x] and [y]. @since 3.0 *) +[@@@endif] +[@@@iflt 5.1] + val hash : t -> int (** [hash x] computes the hash of [x]. Like {!Stdlib.abs (to_int x)}. *) +[@@@endif] + val sign : t -> int (** [sign x] return [0] if [x = 0], [-1] if [x < 0] and [1] if [x > 0]. Same as [compare x zero]. @@ -81,9 +88,6 @@ val of_string : string -> t option (** [of_string s] is the safe version of {!of_string_exn}. Like {!of_string_exn}, but return [None] instead of raising. *) -val of_string_opt : string -> t option -(** [of_string_opt s] is an alias to {!of_string}. *) - val of_string_exn : string -> t (** [of_string_exn s] converts the given string [s] into a 32-bit integer. Alias to {!Int32.of_string}. diff --git a/src/core/CCInt64.ml b/src/core/CCInt64.ml index 80b22e67f..8bb45ead4 100644 --- a/src/core/CCInt64.ml +++ b/src/core/CCInt64.ml @@ -2,8 +2,13 @@ include Int64 +[@@@iflt 4.13] + let min : t -> t -> t = Stdlib.min let max : t -> t -> t = Stdlib.max + +[@@@endif] + let sign i = compare i zero (* use FNV: @@ -126,7 +131,6 @@ let random_range i j st = add i (random (sub j i) st) let of_string_exn = of_string let of_string x = try Some (of_string_exn x) with Failure _ -> None -let of_string_opt = of_string let most_significant_bit = logxor (neg 1L) (shift_right_logical (neg 1L) 1) type output = char -> unit diff --git a/src/core/CCInt64.mli b/src/core/CCInt64.mli index 3466d2899..050553289 100644 --- a/src/core/CCInt64.mli +++ b/src/core/CCInt64.mli @@ -18,6 +18,8 @@ include module type of struct include Int64 end +[@@@iflt 4.13] + val min : t -> t -> t (** [min x y] returns the minimum of the two integers [x] and [y]. @since 3.0 *) @@ -26,10 +28,15 @@ val max : t -> t -> t (** [max x y] returns the maximum of the two integers [x] and [y]. @since 3.0 *) +[@@@endif] +[@@@iflt 5.1] + val hash : t -> int (** [hash x] computes the hash of [x], a non-negative integer. Uses FNV since 3.10 *) +[@@@endif] + val hash_to_int64 : t -> t (** Like {!hash} but does not truncate. Uses FNV. @@ -86,10 +93,6 @@ val of_string : string -> t option (** [of_string s] is the safe version of {!of_string_exn}. Like {!of_string_exn}, but return [None] instead of raising. *) -val of_string_opt : string -> t option -(** [of_string_opt s] is an alias to {!of_string}. - @since 2.1 *) - val of_string_exn : string -> t (** [of_string_exn s] converts the given string [s] into a 64-bit integer. Alias to {!Int64.of_string}. diff --git a/src/core/CCList.ml b/src/core/CCList.ml index 75684ce08..00747c05b 100644 --- a/src/core/CCList.ml +++ b/src/core/CCList.ml @@ -1,43 +1,15 @@ -(* backport new functions from stdlib here *) - -[@@@ocaml.warning "-32"] - -let rec compare_lengths l1 l2 = - match l1, l2 with - | [], [] -> 0 - | [], _ :: _ -> -1 - | _ :: _, [] -> 1 - | _ :: tail1, _ :: tail2 -> compare_lengths tail1 tail2 - -let rec compare_length_with l n = - match l, n with - | _ when n < 0 -> 1 - | [], 0 -> 0 - | [], _ -> -1 - | _ :: tail, _ -> compare_length_with tail (n - 1) - -let rec assoc_opt x = function - | [] -> None - | (y, v) :: _ when Stdlib.( = ) x y -> Some v - | _ :: tail -> assoc_opt x tail - -let rec assq_opt x = function - | [] -> None - | (y, v) :: _ when Stdlib.( == ) x y -> Some v - | _ :: tail -> assq_opt x tail - -[@@@ocaml.warning "+32"] - -(* end of backport *) - include List let empty = [] +[@@@iflt 5.1] + let is_empty = function | [] -> true | _ :: _ -> false +[@@@endif] + let mguard c = if c then [ () ] @@ -391,25 +363,27 @@ let[@tail_mod_cons] rec unfold f seed = | Some (v, next) -> v :: unfold f next [@@@endif] +[@@@iflt 4.12] -let rec compare f l1 l2 = +let rec compare cmp l1 l2 = match l1, l2 with | [], [] -> 0 | _, [] -> 1 | [], _ -> -1 | x1 :: l1', x2 :: l2' -> - let c = f x1 x2 in + let c = cmp x1 x2 in if c <> 0 then c else - compare f l1' l2' + compare cmp l1' l2' -let rec equal f l1 l2 = +let rec equal eq l1 l2 = match l1, l2 with | [], [] -> true | [], _ | _, [] -> false - | x1 :: l1', x2 :: l2' -> f x1 x2 && equal f l1' l2' + | x1 :: l1', x2 :: l2' -> eq x1 x2 && equal eq l1' l2' +[@@@endif] [@@@iflt 5.1] let rec flat_map_kont f l kont = @@ -969,6 +943,8 @@ let find_pred_exn p l = | None -> raise Not_found | Some x -> x +[@@@iflt 5.1] + let find_mapi f l = let rec aux f i = function | [] -> None @@ -979,8 +955,13 @@ let find_mapi f l = in aux f 0 l +[@@@endif] +[@@@iflt 4.10] + let find_map f l = find_mapi (fun _ -> f) l +[@@@endif] + let find_idx p l = find_mapi (fun i x -> @@ -999,6 +980,8 @@ let remove ~eq x l = in remove' eq x [] l +[@@@iflt 5.1] + let filter_map f l = let rec recurse acc l = match l with @@ -1013,6 +996,8 @@ let filter_map f l = in recurse [] l +[@@@endif] + let keep_some l = filter_map (fun x -> x) l let keep_ok l = @@ -1215,6 +1200,9 @@ let inter ~eq l1 l2 = in inter eq [] l1 l2 +[@@@iflt 5.1] + +(* Because our map is tail rec between 4.13 and 5.1 *) let mapi f l = let r = ref 0 in map @@ -1224,6 +1212,8 @@ let mapi f l = y) l +[@@@endif] + let iteri f l = let rec aux f i l = match l with @@ -1547,11 +1537,6 @@ let to_string ?(start = "") ?(stop = "") ?(sep = ", ") item_to_string l = let to_iter l k = List.iter k l -let rec to_seq l () = - match l with - | [] -> Seq.Nil - | x :: tl -> Seq.Cons (x, to_seq tl) - let of_iter i = let l = ref [] in i (fun x -> l := x :: !l); diff --git a/src/core/CCList.mli b/src/core/CCList.mli index f1d31605c..4fcb8dec7 100644 --- a/src/core/CCList.mli +++ b/src/core/CCList.mli @@ -16,10 +16,14 @@ type +'a t = 'a list val empty : 'a t (** [empty] is [[]]. *) +[@@@iflt 5.1] + val is_empty : _ t -> bool (** [is_empty l] returns [true] iff [l = []]. @since 0.11 *) +[@@@endif] + val cons_maybe : 'a option -> 'a t -> 'a t (** [cons_maybe (Some x) l] is [x :: l]. [cons_maybe None l] is [l]. @@ -127,11 +131,6 @@ val count_true_false : ('a -> bool) -> 'a list -> int * int that satisfy the predicate [p], and [int2] the number of elements that do not satisfy [p]. @since 2.4 *) -val init : int -> (int -> 'a) -> 'a t -(** [init len f] is [f 0; f 1; …; f (len-1)]. - @raise Invalid_argument if len < 0. - @since 0.6 *) - val combine : 'a list -> 'b list -> ('a * 'b) list (** [combine [a1; …; an] [b1; …; bn]] is [[(a1,b1); …; (an,bn)]]. Transform two lists into a list of pairs. @@ -161,25 +160,17 @@ val split : ('a * 'b) t -> 'a t * 'b t @since 1.2, but only @since 2.2 with labels *) +[@@@iflt 4.12] + val compare : ('a -> 'a -> int) -> 'a t -> 'a t -> int (** [compare cmp l1 l2] compares the two lists [l1] and [l2] using the given comparison function [cmp]. *) -val compare_lengths : 'a t -> 'b t -> int -(** [compare_lengths l1 l2] compare the lengths of the two lists [l1] and [l2]. - Equivalent to [compare (length l1) (length l2)] but more efficient. - @since 1.5, but only - @since 2.2 with labels *) - -val compare_length_with : 'a t -> int -> int -(** [compare_length_with l x] compares the length of the list [l] to an integer [x]. - Equivalent to [compare (length l) x] but more efficient. - @since 1.5, but only - @since 2.2 with labels *) - val equal : ('a -> 'a -> bool) -> 'a t -> 'a t -> bool (** [equal p l1 l2] returns [true] if [l1] and [l2] are equal. *) +[@@@endif] + val flat_map : ('a -> 'b t) -> 'a t -> 'b t (** [flat_map f l] maps and flattens at the same time (safe). Evaluation order is not guaranteed. *) @@ -437,26 +428,28 @@ val find_pred : ('a -> bool) -> 'a t -> 'a option or returns [None] if no element satisfies [p]. @since 0.11 *) -val find_opt : ('a -> bool) -> 'a t -> 'a option -(** [find_opt p l] is the safe version of {!find}. - @since 1.5, but only - @since 2.2 with labels *) - val find_pred_exn : ('a -> bool) -> 'a t -> 'a (** [find_pred_exn p l] is the unsafe version of {!find_pred}. @raise Not_found if no such element is found. @since 0.11 *) +[@@@iflt 4.10] + val find_map : ('a -> 'b option) -> 'a t -> 'b option (** [find_map f l] traverses [l], applying [f] to each element. If for some element [x], [f x = Some y], then [Some y] is returned. Otherwise the call returns [None]. @since 0.11 *) +[@@@endif] +[@@@iflt 5.1] + val find_mapi : (int -> 'a -> 'b option) -> 'a t -> 'b option (** [find_mapi f l] is like {!find_map}, but also pass the index to the predicate function. @since 0.11 *) +[@@@endif] + val find_idx : ('a -> bool) -> 'a t -> (int * 'a) option (** [find_idx p x] returns [Some (i,x)] where [x] is the [i]-th element of [l], and [p x] holds. Otherwise returns [None]. *) @@ -467,11 +460,6 @@ val remove : eq:('a -> 'a -> bool) -> key:'a -> 'a t -> 'a t @since 0.11 *) (* FIXME: the original CCList.mli uses ~x instead of ~key !! *) -val filter_map : ('a -> 'b option) -> 'a t -> 'b t -(** [filter_map f l] is the sublist of [l] containing only elements for which - [f] returns [Some e]. - Map and remove elements at the same time. *) - val keep_some : 'a option t -> 'a t (** [keep_some l] retains only elements of the form [Some x]. Like [filter_map CCFun.id]. @@ -574,16 +562,6 @@ val group_succ : eq:('a -> 'a -> bool) -> 'a list -> 'a list list (** {2 Indices} *) -val mapi : (int -> 'a -> 'b) -> 'a t -> 'b t -(** [mapi f l] is like {!map}, but the function [f] is applied to the index of - the element as first argument (counting from 0), and the element - itself as second argument. *) - -val iteri : (int -> 'a -> unit) -> 'a t -> unit -(** [iteri f l] is like {!val-iter}, but the function [f] is applied to the index of - the element as first argument (counting from 0), and the element - itself as second argument. *) - val iteri2 : (int -> 'a -> 'b -> unit) -> 'a t -> 'b t -> unit (** [iteri2 f l1 l2] applies [f] to the two lists [l1] and [l2] simultaneously. The integer passed to [f] indicates the index of element. @@ -758,14 +736,6 @@ val assoc_opt : eq:('a -> 'a -> bool) -> 'a -> ('a * 'b) t -> 'b option @since 1.5, but only @since 2.0 with labels *) -val assq_opt : 'a -> ('a * 'b) t -> 'b option -(** [assq_opt k alist] returns [Some v] if the given key [k] is present into [alist]. - Like [Assoc.assoc_opt] but use physical equality instead of structural equality - to compare keys. - Safe version of {!assq}. - @since 1.5, but only - @since 2.0 with labels *) - val mem_assoc : ?eq:('a -> 'a -> bool) -> 'a -> ('a * _) t -> bool (** [mem_assoc ?eq k alist] returns [true] iff [k] is a key in [alist]. Like [Assoc.mem]. @@ -884,11 +854,6 @@ val to_iter : 'a t -> 'a iter (** [to_iter l] returns a [iter] of the elements of the list [l]. @since 2.8 *) -val to_seq : 'a t -> 'a Seq.t -(** [to_seq l] returns a [Seq.t] of the elements of the list [l]. - Renamed from [to_std_seq] since 3.0. - @since 3.0 *) - val of_iter : 'a iter -> 'a t (** [of_iter iter] builds a list from a given [iter]. In the result, elements appear in the same order as they did in the source [iter]. @@ -899,12 +864,6 @@ val of_seq_rev : 'a Seq.t -> 'a t Renamed from [to_std_seq_rev] since 3.0. @since 3.0 *) -val of_seq : 'a Seq.t -> 'a t -(** [of_seq seq] builds a list from a given [Seq.t]. - In the result, elements appear in the same order as they did in the source [Seq.t]. - Renamed from [of_std_seq] since 3.0. - @since 3.0 *) - val to_gen : 'a t -> 'a gen (** [to_gen l] returns a [gen] of the elements of the list [l]. *) diff --git a/src/core/CCListLabels.mli b/src/core/CCListLabels.mli index 83421d6c6..1f75d3fd7 100644 --- a/src/core/CCListLabels.mli +++ b/src/core/CCListLabels.mli @@ -18,18 +18,18 @@ type 'a t = 'a list val empty : 'a t (** [empty] is [[]]. *) +[@@@iflt 5.1] + val is_empty : _ t -> bool (** [is_empty l] returns [true] iff [l = []]. @since 0.11 *) +[@@@endif] + val map : f:('a -> 'b) -> 'a t -> 'b t (** [map ~f [a0; a1; …; an]] applies function [f] in turn to [[a0; a1; …; an]]. Safe version of {!List.map}. *) -val cons : 'a -> 'a t -> 'a t -(** [cons x l] is [x::l]. - @since 0.12 *) - val append : 'a t -> 'a t -> 'a t (** [append l1 l2] returns the list that is the concatenation of [l1] and [l2]. Safe version of {!List.append}. *) @@ -160,11 +160,6 @@ val count_true_false : f:('a -> bool) -> 'a list -> int * int that satisfy the predicate [f], and [int2] the number of elements that do not satisfy [f]. @since 2.4 *) -val init : int -> f:(int -> 'a) -> 'a t -(** [init len ~f] is [f 0; f 1; …; f (len-1)]. - @raise Invalid_argument if len < 0. - @since 0.6 *) - val combine : 'a list -> 'b list -> ('a * 'b) list (** [combine [a1; …; an] [b1; …; bn]] is [[(a1,b1); …; (an,bn)]]. Transform two lists into a list of pairs. @@ -194,25 +189,17 @@ val split : ('a * 'b) t -> 'a t * 'b t @since 1.2, but only @since 2.2 with labels *) -val compare : ('a -> 'a -> int) -> 'a t -> 'a t -> int +[@@@iflt 4.12] + +val compare : cmp:('a -> 'a -> int) -> 'a t -> 'a t -> int (** [compare cmp l1 l2] compares the two lists [l1] and [l2] using the given comparison function [cmp]. *) -val compare_lengths : 'a t -> 'b t -> int -(** [compare_lengths l1 l2] compare the lengths of the two lists [l1] and [l2]. - Equivalent to [compare (length l1) (length l2)] but more efficient. - @since 1.5, but only - @since 2.2 with labels *) - -val compare_length_with : 'a t -> int -> int -(** [compare_length_with l x] compares the length of the list [l] to an integer [x]. - Equivalent to [compare (length l) x] but more efficient. - @since 1.5, but only - @since 2.2 with labels *) - -val equal : ('a -> 'a -> bool) -> 'a t -> 'a t -> bool +val equal : eq:('a -> 'a -> bool) -> 'a t -> 'a t -> bool (** [equal p l1 l2] returns [true] if [l1] and [l2] are equal. *) +[@@@endif] + val flat_map : f:('a -> 'b t) -> 'a t -> 'b t (** [flat_map ~f l] maps and flattens at the same time (safe). Evaluation order is not guaranteed. *) @@ -470,26 +457,28 @@ val find_pred : f:('a -> bool) -> 'a t -> 'a option or returns [None] if no element satisfies [f]. @since 0.11 *) -val find_opt : f:('a -> bool) -> 'a t -> 'a option -(** [find_opt ~f l] is the safe version of {!find}. - @since 1.5, but only - @since 2.2 with labels *) - val find_pred_exn : f:('a -> bool) -> 'a t -> 'a (** [find_pred_exn ~f l] is the unsafe version of {!find_pred}. @raise Not_found if no such element is found. @since 0.11 *) +[@@@iflt 4.10] + val find_map : f:('a -> 'b option) -> 'a t -> 'b option (** [find_map ~f l] traverses [l], applying [f] to each element. If for some element [x], [f x = Some y], then [Some y] is returned. Otherwise the call returns [None]. @since 0.11 *) +[@@@endif] +[@@@iflt 5.1] + val find_mapi : f:(int -> 'a -> 'b option) -> 'a t -> 'b option (** [find_mapi ~f l] is like {!find_map}, but also pass the index to the predicate function. @since 0.11 *) +[@@@endif] + val find_idx : f:('a -> bool) -> 'a t -> (int * 'a) option (** [find_idx ~f x] returns [Some (i,x)] where [x] is the [i]-th element of [l], and [f x] holds. Otherwise returns [None]. *) @@ -501,11 +490,6 @@ val remove : @since 0.11 *) (* FIXME: the original CCList.mli uses ~x instead of ~key !! *) -val filter_map : f:('a -> 'b option) -> 'a t -> 'b t -(** [filter_map ~f l] is the sublist of [l] containing only elements for which - [f] returns [Some e]. - Map and remove elements at the same time. *) - val keep_some : 'a option t -> 'a t (** [keep_some l] retains only elements of the form [Some x]. Like [filter_map CCFun.id]. @@ -612,16 +596,6 @@ val group_succ : eq:(('a -> 'a -> bool)[@keep_label]) -> 'a list -> 'a list list (** {2 Indices} *) -val mapi : f:(int -> 'a -> 'b) -> 'a t -> 'b t -(** [mapi ~f l] is like {!map}, but the function [f] is applied to the index of - the element as first argument (counting from 0), and the element - itself as second argument. *) - -val iteri : f:(int -> 'a -> unit) -> 'a t -> unit -(** [iteri ~f l] is like {!iter}, but the function [f] is applied to the index of - the element as first argument (counting from 0), and the element - itself as second argument. *) - val iteri2 : f:(int -> 'a -> 'b -> unit) -> 'a t -> 'b t -> unit (** [iteri2 ~f l1 l2] applies [f] to the two lists [l1] and [l2] simultaneously. The integer passed to [f] indicates the index of element. @@ -900,11 +874,6 @@ val to_iter : 'a t -> 'a iter (** [to_iter l] returns a [iter] of the elements of the list [l]. @since 2.8 *) -val to_seq : 'a t -> 'a Seq.t -(** [to_seq l] returns a [Seq.t] of the elements of the list [l]. - Renamed from [to_std_seq] since 3.0. - @since 3.0 *) - val of_iter : 'a iter -> 'a t (** [of_iter iter] builds a list from a given [iter]. In the result, elements appear in the same order as they did in the source [iter]. @@ -915,12 +884,6 @@ val of_seq_rev : 'a Seq.t -> 'a t Renamed from [of_std_seq_rev] since 3.0. @since 3.0 *) -val of_seq : 'a Seq.t -> 'a t -(** [of_seq seq] builds a list from a given [Seq.t]. - In the result, elements appear in the same order as they did in the source [Seq.t]. - Renamed from [of_std_seq] since 3.0. - @since 3.0 *) - val to_gen : 'a t -> 'a gen (** [to_gen l] returns a [gen] of the elements of the list [l]. *) diff --git a/tests/core/t_float.ml b/tests/core/t_float.ml index 0575b80c1..20bdda479 100644 --- a/tests/core/t_float.ml +++ b/tests/core/t_float.ml @@ -2,10 +2,10 @@ open CCFloat module T = (val Containers_testlib.make ~__FILE__ ()) include T;; -t @@ fun () -> max nan 1. = 1.;; -t @@ fun () -> min nan 1. = 1.;; -t @@ fun () -> max 1. nan = 1.;; -t @@ fun () -> min 1. nan = 1.;; +t @@ fun () -> is_nan (max nan 1.);; +t @@ fun () -> is_nan (min nan 1.);; +t @@ fun () -> is_nan (max 1. nan);; +t @@ fun () -> is_nan (min 1. nan);; q Q.(pair float float)