Skip to content

Commit

Permalink
v0.18~preview.130.00+55
Browse files Browse the repository at this point in the history
  • Loading branch information
public-release committed Oct 8, 2024
1 parent c22f3ad commit 6ddf343
Show file tree
Hide file tree
Showing 67 changed files with 8,318 additions and 8,519 deletions.
2 changes: 1 addition & 1 deletion src/array.mli
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ include Ppx_compare_lib.Equal.S_local1 with type 'a t := 'a t

val globalize : ('a -> 'a) -> 'a t -> 'a t

include Sexplib0.Sexpable.S1 with type 'a t := 'a t
include Sexplib0.Sexpable.S_any1 with type 'a t := 'a t

val t_sexp_grammar : 'a Sexplib0.Sexp_grammar.t -> 'a t Sexplib0.Sexp_grammar.t

Expand Down
2 changes: 1 addition & 1 deletion src/bool.mli
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ include Ppx_enumerate_lib.Enumerable.S with type t := t

val globalize : t -> t

include Sexplib0.Sexpable.S with type t := t
include Sexplib0.Sexpable.S_any with type t := t

val t_sexp_grammar : t Sexplib0.Sexp_grammar.t

Expand Down
2 changes: 1 addition & 1 deletion src/bytes_intf.ml
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ module type Bytes = sig

val globalize : t -> t

include Sexplib0.Sexpable.S with type t := t
include Sexplib0.Sexpable.S_any with type t := t

val t_sexp_grammar : t Sexplib0.Sexp_grammar.t

Expand Down
4 changes: 2 additions & 2 deletions src/char.mli
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ include Ppx_enumerate_lib.Enumerable.S with type t := t

val globalize : t -> t

include Sexplib0.Sexpable.S with type t := t
include Sexplib0.Sexpable.S_any with type t := t

val t_sexp_grammar : t Sexplib0.Sexp_grammar.t

Expand Down Expand Up @@ -95,7 +95,7 @@ module Caseless : sig
type nonrec t = t [@@deriving_inline hash, sexp, sexp_grammar]

include Ppx_hash_lib.Hashable.S with type t := t
include Sexplib0.Sexpable.S with type t := t
include Sexplib0.Sexpable.S_any with type t := t

val t_sexp_grammar : t Sexplib0.Sexp_grammar.t

Expand Down
5 changes: 4 additions & 1 deletion src/dictionary_mutable_intf.ml
Original file line number Diff line number Diff line change
Expand Up @@ -381,7 +381,10 @@ module Definitions = struct
-> ('key, 'c, 'phantom) t * ('key, 'd, 'phantom) t

(** Merges two dictionaries by fully traversing both. Not suitable for efficiently
merging lists of dictionaries. See [merge_into] instead. *)
merging lists of dictionaries. See [merge_into] instead.
If the two dictionaries differ in their implementations, e.g. of [hash] or
[compare] functions, those from the first argument are preferred. *)
val merge
: ( ('key, 'data1, 'phantom) t
-> ('key, 'data2, 'phantom) t
Expand Down
7 changes: 4 additions & 3 deletions src/exn.ml
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ let () =

[@@@end]

exception Sexp of Sexp.t
exception Sexp of Sexp.t Lazy.t

(* We install a custom exn-converter rather than use:
Expand All @@ -47,13 +47,14 @@ exception Sexp of Sexp.t
to eliminate the extra wrapping of [(Sexp ...)]. *)
let () =
Sexplib0.Sexp_conv.Exn_converter.add [%extension_constructor Sexp] (function
| Sexp t -> t
| Sexp t -> Lazy.force t
| _ ->
(* Reaching this branch indicates a bug in sexplib. *)
assert false)
;;

let create_s sexp = Sexp sexp
let create_s sexp = Sexp (Lazy.from_val sexp)
let create_s_lazy lazy_sexp = Sexp lazy_sexp

let raise_with_original_backtrace t backtrace =
Stdlib.Printexc.raise_with_backtrace t backtrace
Expand Down
3 changes: 3 additions & 0 deletions src/exn.mli
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,9 @@ exception Reraised of string * t
particular exn constructor doesn't matter. *)
val create_s : Sexp.t -> t

(** [create_s_lazy lazy_sexp] is like [create_s], but takes a lazily generated sexp. *)
val create_s_lazy : Sexp.t Lazy.t -> t

(** Same as [raise], except that the backtrace is not recorded. *)
val raise_without_backtrace : t -> _

Expand Down
2 changes: 1 addition & 1 deletion src/float.mli
Original file line number Diff line number Diff line change
Expand Up @@ -700,7 +700,7 @@ val ieee_mantissa : t -> Int63.t
module Terse : sig
type nonrec t = t [@@deriving_inline sexp, sexp_grammar]

include Sexplib0.Sexpable.S with type t := t
include Sexplib0.Sexpable.S_any with type t := t

val t_sexp_grammar : t Sexplib0.Sexp_grammar.t

Expand Down
2 changes: 1 addition & 1 deletion src/hash_set_intf.ml
Original file line number Diff line number Diff line change
Expand Up @@ -172,7 +172,7 @@ module type Hash_set = sig
module Poly : sig
type nonrec 'a t = 'a t [@@deriving_inline sexp, sexp_grammar]

include Sexplib0.Sexpable.S1 with type 'a t := 'a t
include Sexplib0.Sexpable.S_any1 with type 'a t := 'a t

val t_sexp_grammar : 'a Sexplib0.Sexp_grammar.t -> 'a t Sexplib0.Sexp_grammar.t

Expand Down
4 changes: 1 addition & 3 deletions src/hashtbl.ml
Original file line number Diff line number Diff line change
Expand Up @@ -638,11 +638,9 @@ let merge =
let maybe_set t ~key ~f d =
match f ~key d with
| None -> ()
| Some v -> set t ~key ~data:v
| Some v -> add_exn t ~key ~data:v
in
fun t_left t_right ~f ->
if not (Hashable.equal t_left.hashable t_right.hashable)
then invalid_arg "Hashtbl.merge: different 'hashable' values";
let new_t =
create
~growth_allowed:t_left.growth_allowed
Expand Down
21 changes: 21 additions & 0 deletions src/indexed_container.ml
Original file line number Diff line number Diff line change
Expand Up @@ -152,6 +152,27 @@ struct
let filteri t ~f =
filter_mapi t ~f:(fun i x -> if f i x then Some x else None) [@nontail]
;;

let partition_mapi t ~f =
let array = Array.mapi (to_array t) ~f in
let xs =
Array.fold_right array ~init:[] ~f:(fun either acc ->
match (either : _ Either0.t) with
| First x -> x :: acc
| Second _ -> acc)
in
let ys =
Array.fold_right array ~init:[] ~f:(fun either acc ->
match (either : _ Either0.t) with
| First _ -> acc
| Second x -> x :: acc)
in
of_list xs, of_list ys
;;

let partitioni_tf t ~f =
partition_mapi t ~f:(fun i x -> if f i x then First x else Second x) [@nontail]
;;
end

module Make_with_creators (T : Make_with_creators_arg) = struct
Expand Down
26 changes: 26 additions & 0 deletions src/indexed_container_intf.ml
Original file line number Diff line number Diff line change
Expand Up @@ -71,6 +71,14 @@ module type S0_with_creators = sig
(** [concat_mapi t ~f] is like concat_map. Additionally, it passes the index as an
argument. *)
val concat_mapi : t -> f:(int -> elt -> t) -> t

(** [partitioni_tf t ~f] is like partition_tf. Additionally, it passes the index as an
argument. *)
val partitioni_tf : t -> f:(int -> elt -> bool) -> t * t

(** [partition_mapi t ~f] is like partition_map. Additionally, it passes the index as an
argument. *)
val partition_mapi : t -> f:(int -> elt -> (elt, elt) Either0.t) -> t * t
end

module type S1_with_creators = sig
Expand All @@ -94,6 +102,14 @@ module type S1_with_creators = sig
(** [concat_mapi t ~f] is like concat_map. Additionally, it passes the index as an
argument. *)
val concat_mapi : 'a t -> f:(int -> 'a -> 'b t) -> 'b t

(** [partitioni_tf t ~f] is like partition_tf. Additionally, it passes the index as an
argument. *)
val partitioni_tf : 'a t -> f:(int -> 'a -> bool) -> 'a t * 'a t

(** [partition_mapi t ~f] is like partition_map. Additionally, it passes the index as an
argument. *)
val partition_mapi : 'a t -> f:(int -> 'a -> ('b, 'c) Either0.t) -> 'b t * 'c t
end

module type Generic_with_creators = sig
Expand All @@ -117,6 +133,16 @@ module type Generic_with_creators = sig
: ('a, 'p1, 'p2) t
-> f:(int -> 'a elt -> ('b, 'p1, 'p2) t)
-> ('b, 'p1, 'p2) t

val partitioni_tf
: ('a, 'p1, 'p2) t
-> f:(int -> 'a elt -> bool)
-> ('a, 'p1, 'p2) t * ('a, 'p1, 'p2) t

val partition_mapi
: ('a, 'p1, 'p2) t
-> f:(int -> 'a elt -> ('b elt, 'c elt) Either0.t)
-> ('b, 'p1, 'p2) t * ('c, 'p1, 'p2) t
end

module type Make_gen_arg = sig
Expand Down
2 changes: 1 addition & 1 deletion src/lazy.mli
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ include Ppx_compare_lib.Equal.S_local1 with type 'a t := 'a t
val globalize : ('a -> 'a) -> 'a t -> 'a t

include Ppx_hash_lib.Hashable.S1 with type 'a t := 'a t
include Sexplib0.Sexpable.S1 with type 'a t := 'a t
include Sexplib0.Sexpable.S_any1 with type 'a t := 'a t

val t_sexp_grammar : 'a Sexplib0.Sexp_grammar.t -> 'a t Sexplib0.Sexp_grammar.t

Expand Down
17 changes: 17 additions & 0 deletions src/list.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1181,6 +1181,23 @@ let partition_tf t ~f =

let partition_result t = partition_map t ~f:Result.to_either

let partition_mapi t ~f =
let rec loop i t fst snd =
match t with
| [] -> rev fst, rev snd
| x :: t ->
(match (f i x : _ Either0.t) with
| First y -> loop (i + 1) t (y :: fst) snd
| Second y -> loop (i + 1) t fst (y :: snd))
in
loop 0 t [] [] [@nontail]
;;

let partitioni_tf t ~f =
let f i x : _ Either.t = if f i x then First x else Second x in
partition_mapi t ~f [@nontail]
;;

module Assoc = struct
type 'a key = ('a[@tag Sexplib0.Sexp_grammar.assoc_key_tag = List []])
[@@deriving_inline sexp, sexp_grammar]
Expand Down
4 changes: 2 additions & 2 deletions src/list.mli
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@ include Ppx_compare_lib.Equal.S_local1 with type 'a t := 'a t
val globalize : ('a -> 'a) -> 'a t -> 'a t

include Ppx_hash_lib.Hashable.S1 with type 'a t := 'a t
include Sexplib0.Sexpable.S1 with type 'a t := 'a t
include Sexplib0.Sexpable.S_any1 with type 'a t := 'a t

val t_sexp_grammar : 'a Sexplib0.Sexp_grammar.t -> 'a t Sexplib0.Sexp_grammar.t

Expand Down Expand Up @@ -401,7 +401,7 @@ val filter_opt : 'a option t -> 'a t
module Assoc : sig
type ('a, 'b) t = ('a * 'b) list [@@deriving_inline sexp, sexp_grammar]

include Sexplib0.Sexpable.S2 with type ('a, 'b) t := ('a, 'b) t
include Sexplib0.Sexpable.S_any2 with type ('a, 'b) t := ('a, 'b) t

val t_sexp_grammar
: 'a Sexplib0.Sexp_grammar.t
Expand Down
2 changes: 1 addition & 1 deletion src/map_intf.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1323,7 +1323,7 @@ module type Map = sig

include Ppx_compare_lib.Comparable.S2 with type ('k, 'v) t := ('k, 'v) t
include Ppx_compare_lib.Equal.S2 with type ('k, 'v) t := ('k, 'v) t
include Sexplib0.Sexpable.S2 with type ('k, 'v) t := ('k, 'v) t
include Sexplib0.Sexpable.S_any2 with type ('k, 'v) t := ('k, 'v) t

val t_sexp_grammar
: 'k Sexplib0.Sexp_grammar.t
Expand Down
2 changes: 1 addition & 1 deletion src/option.ml
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,7 @@ sig
val globalize : ('a -> 'a) -> 'a t -> 'a t

include Ppx_hash_lib.Hashable.S1 with type 'a t := 'a t
include Sexplib0.Sexpable.S1 with type 'a t := 'a t
include Sexplib0.Sexpable.S_any1 with type 'a t := 'a t

val t_sexp_grammar : 'a Sexplib0.Sexp_grammar.t -> 'a t Sexplib0.Sexp_grammar.t

Expand Down
2 changes: 1 addition & 1 deletion src/or_error.mli
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@ include Ppx_compare_lib.Equal.S_local1 with type 'a t := 'a t
val globalize : ('a -> 'a) -> 'a t -> 'a t

include Ppx_hash_lib.Hashable.S1 with type 'a t := 'a t
include Sexplib0.Sexpable.S1 with type 'a t := 'a t
include Sexplib0.Sexpable.S_any1 with type 'a t := 'a t

val t_sexp_grammar : 'a Sexplib0.Sexp_grammar.t -> 'a t Sexplib0.Sexp_grammar.t

Expand Down
2 changes: 1 addition & 1 deletion src/ref.ml
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ sig

val globalize : ('a -> 'a) -> 'a t -> 'a t

include Sexplib0.Sexpable.S1 with type 'a t := 'a t
include Sexplib0.Sexpable.S_any1 with type 'a t := 'a t

val t_sexp_grammar : 'a Sexplib0.Sexp_grammar.t -> 'a t Sexplib0.Sexp_grammar.t

Expand Down
Loading

0 comments on commit 6ddf343

Please sign in to comment.