diff --git a/src/Iter.ml b/src/Iter.ml index 406b2ab..8c25627 100644 --- a/src/Iter.ml +++ b/src/Iter.ml @@ -255,7 +255,7 @@ module MList = struct | Cons of 'a array * int ref * 'a node ref (* build and call callback on every element *) - let of_seq_with seq k = + let of_iter_with seq k = let start = ref Nil in let chunk_size = ref 8 in (* fill the list. prev: tail-reference from previous node *) @@ -279,8 +279,8 @@ module MList = struct !prev := !cur; !start - let of_seq seq = - of_seq_with seq (fun _ -> ()) + let of_iter seq = + of_iter_with seq (fun _ -> ()) let rec iter f l = match l with | Nil -> () @@ -314,7 +314,7 @@ module MList = struct | Cons (a, n, _) when i < !n -> a.(i) | Cons (_, n, tl) -> get !tl (i- !n) - let to_seq l k = iter k l + let to_iter l k = iter k l let _to_next arg l = let cur = ref l in @@ -345,8 +345,8 @@ module MList = struct end let persistent seq = - let l = MList.of_seq seq in - MList.to_seq l + let l = MList.of_iter seq in + MList.to_iter l (*$R let printer = pp_ilist in @@ -388,8 +388,8 @@ let persistent_lazy (seq:'a t) = | LazyCached seq' -> seq' k | LazySuspend -> (* here if this traversal is interruted, no caching occurs *) - let seq' = MList.of_seq_with seq k in - r := LazyCached (MList.to_seq seq') + let seq' = MList.of_iter_with seq k in + r := LazyCached (MList.to_iter seq') let sort ?(cmp=Pervasives.compare) seq = (* use an intermediate list, then sort the list *) @@ -869,7 +869,7 @@ let drop_while p seq k = else k x) let rev seq = - let l = MList.of_seq seq in + let l = MList.of_iter seq in fun k -> MList.iter_rev k l (*$R @@ -1007,7 +1007,7 @@ let of_opt o k = match o with | Some x -> k x let to_array seq = - let l = MList.of_seq seq in + let l = MList.of_iter seq in let n = MList.length l in if n = 0 then [||] @@ -1033,7 +1033,7 @@ let array_slice a i j k = let of_stream s k = Stream.iter k s let to_stream seq = - let l = MList.of_seq seq in + let l = MList.of_iter seq in MList.to_stream l let to_stack s seq = iter (fun x -> Stack.push x s) seq @@ -1166,11 +1166,11 @@ let of_gen g = | None -> () | Some x -> k x; iter1 k in - let l = MList.of_seq iter1 in - MList.to_seq l + let l = MList.of_iter iter1 in + MList.to_iter l let to_gen seq = - let l = MList.of_seq seq in + let l = MList.of_iter seq in MList.to_gen l let rec of_klist l k = match l() with @@ -1178,7 +1178,7 @@ let rec of_klist l k = match l() with | `Cons (x,tl) -> k x; of_klist tl k let to_klist seq = - let l = MList.of_seq seq in + let l = MList.of_iter seq in MList.to_klist l (** {2 Functorial conversions between sets and iterators} *) @@ -1186,21 +1186,21 @@ let to_klist seq = module Set = struct module type S = sig include Set.S - val of_seq : elt iter -> t - val to_seq : t -> elt iter + val of_iter : elt iter -> t + val to_iter : t -> elt iter val to_list : t -> elt list val of_list : elt list -> t end (** Create an enriched Set module from the given one *) module Adapt(X : Set.S) : S with type elt = X.elt and type t = X.t = struct - let to_seq_ set k = X.iter k set - let of_seq_ seq = fold (fun set x -> X.add x set) X.empty seq + let to_iter_ set k = X.iter k set + let of_iter_ seq = fold (fun set x -> X.add x set) X.empty seq include X - let to_seq = to_seq_ - let of_seq = of_seq_ + let to_iter = to_iter_ + let of_iter = of_iter_ let of_list l = List.fold_left (fun set x -> add x set) empty l let to_list = elements end @@ -1217,8 +1217,8 @@ end module Map = struct module type S = sig include Map.S - val to_seq : 'a t -> (key * 'a) iter - val of_seq : (key * 'a) iter -> 'a t + val to_iter : 'a t -> (key * 'a) iter + val of_iter : (key * 'a) iter -> 'a t val keys : 'a t -> key iter val values : 'a t -> 'a iter val to_list : 'a t -> (key * 'a) list @@ -1227,21 +1227,21 @@ module Map = struct (** Adapt a pre-existing Map module to make it iterator-aware *) module Adapt(M : Map.S) = struct - let to_seq_ m = from_iter (fun k -> M.iter (fun x y -> k (x,y)) m) + let to_iter_ m = from_iter (fun k -> M.iter (fun x y -> k (x,y)) m) - let of_seq_ seq = fold (fun m (k,v) -> M.add k v m) M.empty seq + let of_iter_ seq = fold (fun m (k,v) -> M.add k v m) M.empty seq let keys m = from_iter (fun k -> M.iter (fun x _ -> k x) m) let values m = from_iter (fun k -> M.iter (fun _ y -> k y) m) - let of_list l = of_seq_ (of_list l) + let of_list l = of_iter_ (of_list l) - let to_list x = to_list (to_seq_ x) + let to_list x = to_list (to_iter_ x) include M - let to_seq = to_seq_ - let of_seq = of_seq_ + let to_iter = to_iter_ + let of_iter = of_iter_ end (** Create an enriched Map module, with iterator-aware functions *) diff --git a/src/Iter.mli b/src/Iter.mli index 6585e09..81394fa 100644 --- a/src/Iter.mli +++ b/src/Iter.mli @@ -5,7 +5,7 @@ (** The iterators are designed to allow easy transfer (mappings) between data structures, without defining [n^2] conversions between the [n] types. The - implementation relies on the assumption that a sequence can be iterated + implementation relies on the assumption that an iterator can be iterated on as many times as needed; this choice allows for high performance of many combinators. However, for transient iterators, the {!persistent} function is provided, storing elements of a transient iterator @@ -18,21 +18,23 @@ Most functions are {b lazy}, i.e. they do not actually use their arguments until their result is iterated on. For instance, if one calls {!map} - on a sequence, one gets a new sequence, but nothing else happens until + on an iterator, one gets a new sequence, but nothing else happens until this new sequence is used (by folding or iterating on it). - If a sequence is built from an iteration function that is {b repeatable} + If an iterator is built from an iteration function that is {b repeatable} (i.e. calling it several times always iterates on the same set of elements, for instance List.iter or Map.iter), then the resulting {!t} object is also repeatable. For {b one-time iter functions} such as iteration on a file descriptor or a {!Stream}, the {!persistent} function can be used to iterate and store elements in - a memory structure; the result is a sequence that iterates on the elements - of this memory structure, cheaply and repeatably. *) + a memory structure; the result is an iterator that iterates on the elements + of this memory structure, cheaply and repeatably. + +*) type +'a t = ('a -> unit) -> unit -(** A sequence of values of type ['a]. If you give it a function ['a -> unit] - it will be applied to every element of the sequence successively. *) +(** An iterator of values of type ['a]. If you give it a function ['a -> unit] + it will be applied to every element of the iterator successively. *) type +'a iter = 'a t @@ -42,10 +44,10 @@ type +'a iter = 'a t type 'a equal = 'a -> 'a -> bool type 'a hash = 'a -> int -(** {2 Build a sequence} *) +(** {2 Build an iterator} *) val from_iter : (('a -> unit) -> unit) -> 'a t -(** Build a sequence from a iter function *) +(** Build an iterator from a iter function *) val from_fun : (unit -> 'a option) -> 'a t (** Call the function repeatedly until it returns None. This @@ -95,7 +97,7 @@ val cycle : 'a t -> 'a t infinite sequence, you should use something like {!take} not to loop forever. *) -(** {2 Consume a sequence} *) +(** {2 Consume an iterator} *) val iter : ('a -> unit) -> 'a t -> unit (** Consume the sequence, passing all its arguments to the function. @@ -175,7 +177,7 @@ val length : 'a t -> int val is_empty : 'a t -> bool (** Is the sequence empty? Forces the sequence. *) -(** {2 Transform a sequence} *) +(** {2 Transform an iterator} *) val filter : ('a -> bool) -> 'a t -> 'a t (** Filter on elements of the sequence *) @@ -190,7 +192,7 @@ val append_l : 'a t list -> 'a t @since 0.11 *) val concat : 'a t t -> 'a t -(** Concatenate a sequence of sequences into one sequence. *) +(** Concatenate an iterator of sequences into one sequence. *) val flatten : 'a t t -> 'a t (** Alias for {!concat} *) @@ -485,7 +487,7 @@ val rev : 'a t -> 'a t val zip_i : 'a t -> (int * 'a) t (** Zip elements of the sequence with their index in the sequence. - Changed type @since 1.0 to just give a sequence of pairs *) + Changed type @since 1.0 to just give an iterator of pairs *) val fold2 : ('c -> 'a -> 'b -> 'c) -> 'c -> ('a * 'b) t -> 'c @@ -565,7 +567,7 @@ val hashtbl_replace : ('a, 'b) Hashtbl.t -> ('a * 'b) t -> unit Hashtbl.replace (erases conflicting bindings) *) val to_hashtbl : ('a * 'b) t -> ('a, 'b) Hashtbl.t -(** Build a hashtable from a sequence of key/value pairs *) +(** Build a hashtable from an iterator of key/value pairs *) val of_hashtbl : ('a, 'b) Hashtbl.t -> ('a * 'b) t (** Iterator of key/value pairs from the hashtable *) @@ -613,7 +615,7 @@ val bools : bool t @since 0.7 *) val of_set : (module Set.S with type elt = 'a and type t = 'b) -> 'b -> 'a t -(** Convert the given set to a sequence. The set module must be provided. *) +(** Convert the given set to an iterator. The set module must be provided. *) val to_set : (module Set.S with type elt = 'a and type t = 'b) -> 'a t -> 'b (** Convert the sequence to a set, given the proper set module *) @@ -622,7 +624,7 @@ type 'a gen = unit -> 'a option type 'a klist = unit -> [`Nil | `Cons of 'a * 'a klist] val of_gen : 'a gen -> 'a t -(** Traverse eagerly the generator and build a sequence from it *) +(** Traverse eagerly the generator and build an iterator from it *) val to_gen : 'a t -> 'a gen (** Make the sequence persistent (O(n)) and then iterate on it. Eager. *) @@ -638,8 +640,8 @@ val to_klist : 'a t -> 'a klist module Set : sig module type S = sig include Set.S - val of_seq : elt iter -> t - val to_seq : t -> elt iter + val of_iter : elt iter -> t + val to_iter : t -> elt iter val to_list : t -> elt list val of_list : elt list -> t end @@ -656,8 +658,8 @@ end module Map : sig module type S = sig include Map.S - val to_seq : 'a t -> (key * 'a) iter - val of_seq : (key * 'a) iter -> 'a t + val to_iter : 'a t -> (key * 'a) iter + val of_iter : (key * 'a) iter -> 'a t val keys : 'a t -> key iter val values : 'a t -> 'a iter val to_list : 'a t -> (key * 'a) list @@ -695,7 +697,7 @@ val shuffle : 'a t -> 'a t @since 0.7 *) val shuffle_buffer : int -> 'a t -> 'a t -(** [shuffle_buffer n seq] returns a sequence of element of [seq] in random +(** [shuffle_buffer n seq] returns an iterator of element of [seq] in random order. The shuffling is *not* uniform. Uses O(n) memory. The first [n] elements of the sequence are consumed immediately. The @@ -746,7 +748,7 @@ include module type of Infix val pp_seq : ?sep:string -> (Format.formatter -> 'a -> unit) -> Format.formatter -> 'a t -> unit -(** Pretty print a sequence of ['a], using the given pretty printer +(** Pretty print an iterator of ['a], using the given pretty printer to print each elements. An optional separator string can be provided. *) val pp_buf : ?sep:string -> (Buffer.t -> 'a -> unit) -> @@ -760,7 +762,7 @@ val to_string : ?sep:string -> ('a -> string) -> 'a t -> string Very basic interface to manipulate files as sequence of chunks/lines. The sequences take care of opening and closing files properly; every time - one iterates over a sequence, the file is opened/closed again. + one iterates over an iterator, the file is opened/closed again. Example: copy a file ["a"] into file ["b"], removing blank lines: diff --git a/src/IterLabels.mli b/src/IterLabels.mli index 1abce16..6c21866 100644 --- a/src/IterLabels.mli +++ b/src/IterLabels.mli @@ -9,8 +9,8 @@ @since 0.5.5 *) type +'a t = ('a -> unit) -> unit -(** A sequence of values of type ['a]. If you give it a function ['a -> unit] - it will be applied to every element of the sequence successively. *) +(** An iterator of values of type ['a]. If you give it a function ['a -> unit] + it will be applied to every element of the iterator successively. *) type +'a iter = 'a t @@ -20,10 +20,10 @@ type +'a iter = 'a t type 'a equal = 'a -> 'a -> bool type 'a hash = 'a -> int -(** {2 Build a sequence} *) +(** {2 Build an iterator} *) val from_iter : (('a -> unit) -> unit) -> 'a t -(** Build a sequence from a iter function *) +(** Build an iterator from a iter function *) val from_fun : (unit -> 'a option) -> 'a t (** Call the function repeatedly until it returns None. This @@ -73,7 +73,7 @@ val cycle : 'a t -> 'a t infinite sequence, you should use something like {!take} not to loop forever. *) -(** {2 Consume a sequence} *) +(** {2 Consume an iterator} *) val iter : f:('a -> unit) -> 'a t -> unit (** Consume the sequence, passing all its arguments to the function. @@ -153,7 +153,7 @@ val length : 'a t -> int val is_empty : 'a t -> bool (** Is the sequence empty? Forces the sequence. *) -(** {2 Transform a sequence} *) +(** {2 Transform an iterator} *) val filter : f:('a -> bool) -> 'a t -> 'a t (** Filter on elements of the sequence *) @@ -168,7 +168,7 @@ val append_l : 'a t list -> 'a t @since 0.11 *) val concat : 'a t t -> 'a t -(** Concatenate a sequence of sequences into one sequence. *) +(** Concatenate an iterator of sequences into one sequence. *) val flatten : 'a t t -> 'a t (** Alias for {!concat} *) @@ -180,13 +180,6 @@ val flat_map_l : f:('a -> 'b list) -> 'a t -> 'b t (** Convenience function combining {!flat_map} and {!of_list} @since 0.9 *) -val filter_map : f:('a -> 'b option) -> 'a t -> 'b t -(** Alias to {!fmap} with a more explicit name *) - -val filter_mapi : f:(int -> 'a -> 'b option) -> 'a t -> 'b t -(** Map with indices, and only keep non-[None] elements - @since 0.11 *) - val seq_list : 'a t list -> 'a list t (** [seq_list l] returns all the ways to pick one element in each sub-sequence in [l]. Assumes the sub-sequences can be iterated on several times. @@ -197,6 +190,14 @@ val seq_list_map : f:('a -> 'b t) -> 'a list -> 'b list t then calls {!seq_list} @since 0.11 *) +val filter_map : f:('a -> 'b option) -> 'a t -> 'b t +(** Map and only keep non-[None] elements + Formerly [fmap] *) + +val filter_mapi : f:(int -> 'a -> 'b option) -> 'a t -> 'b t +(** Map with indices, and only keep non-[None] elements + @since 0.11 *) + val filter_count : f:('a -> bool) -> 'a t -> int (** Count how many elements satisfy the given predicate @since 1.0 *) @@ -457,7 +458,7 @@ val rev : 'a t -> 'a t val zip_i : 'a t -> (int * 'a) t (** Zip elements of the sequence with their index in the sequence. - Changed type @since 1.0 to just give a sequence of pairs *) + Changed type @since 1.0 to just give an iterator of pairs *) val fold2 : f:('c -> 'a -> 'b -> 'c) -> init:'c -> ('a * 'b) t -> 'c @@ -537,7 +538,7 @@ val hashtbl_replace : ('a, 'b) Hashtbl.t -> ('a * 'b) t -> unit Hashtbl.replace (erases conflicting bindings) *) val to_hashtbl : ('a * 'b) t -> ('a, 'b) Hashtbl.t -(** Build a hashtable from a sequence of key/value pairs *) +(** Build a hashtable from an iterator of key/value pairs *) val of_hashtbl : ('a, 'b) Hashtbl.t -> ('a * 'b) t (** Iterator of key/value pairs from the hashtable *) @@ -586,7 +587,7 @@ val bools : bool t @since 0.9 *) val of_set : (module Set.S with type elt = 'a and type t = 'b) -> 'b -> 'a t -(** Convert the given set to a sequence. The set module must be provided. *) +(** Convert the given set to an iterator. The set module must be provided. *) val to_set : (module Set.S with type elt = 'a and type t = 'b) -> 'a t -> 'b (** Convert the sequence to a set, given the proper set module *) @@ -595,7 +596,7 @@ type 'a gen = unit -> 'a option type 'a klist = unit -> [`Nil | `Cons of 'a * 'a klist] val of_gen : 'a gen -> 'a t -(** Traverse eagerly the generator and build a sequence from it *) +(** Traverse eagerly the generator and build an iterator from it *) val to_gen : 'a t -> 'a gen (** Make the sequence persistent (O(n)) and then iterate on it. Eager. *) @@ -611,8 +612,8 @@ val to_klist : 'a t -> 'a klist module Set : sig module type S = sig include Set.S - val of_seq : elt iter -> t - val to_seq : t -> elt iter + val of_iter : elt iter -> t + val to_iter : t -> elt iter val to_list : t -> elt list val of_list : elt list -> t end @@ -629,8 +630,8 @@ end module Map : sig module type S = sig include Map.S - val to_seq : 'a t -> (key * 'a) iter - val of_seq : (key * 'a) iter -> 'a t + val to_iter : 'a t -> (key * 'a) iter + val of_iter : (key * 'a) iter -> 'a t val keys : 'a t -> key iter val values : 'a t -> 'a iter val to_list : 'a t -> (key * 'a) list @@ -668,7 +669,7 @@ val shuffle : 'a t -> 'a t @since 0.7 *) val shuffle_buffer : n:int -> 'a t -> 'a t -(** [shuffle_buffer n seq] returns a sequence of element of [seq] in random +(** [shuffle_buffer n seq] returns an iterator of element of [seq] in random order. The shuffling is not uniform. Uses O(n) memory. The first [n] elements of the sequence are consumed immediately. The @@ -715,12 +716,11 @@ end include module type of Infix - (** {2 Pretty printing of sequences} *) val pp_seq : ?sep:string -> (Format.formatter -> 'a -> unit) -> Format.formatter -> 'a t -> unit -(** Pretty print a sequence of ['a], using the given pretty printer +(** Pretty print an iterator of ['a], using the given pretty printer to print each elements. An optional separator string can be provided. *) val pp_buf : ?sep:string -> (Buffer.t -> 'a -> unit) -> @@ -734,7 +734,7 @@ val to_string : ?sep:string -> ('a -> string) -> 'a t -> string Very basic interface to manipulate files as sequence of chunks/lines. The sequences take care of opening and closing files properly; every time - one iterates over a sequence, the file is opened/closed again. + one iterates over an iterator, the file is opened/closed again. Example: copy a file ["a"] into file ["b"], removing blank lines: