style and license headers

This commit is contained in:
Simon Cruanes 2016-01-08 20:41:18 +01:00
parent ae1932fba4
commit 117755aa33
4 changed files with 519 additions and 594 deletions

View file

@ -1,4 +1,4 @@
Copyright (c) 2012, Simon Cruanes Copyright (c) 2012-2016, Simon Cruanes
All rights reserved. All rights reserved.
Redistribution and use in source and binary forms, with or without Redistribution and use in source and binary forms, with or without

View file

@ -1,29 +1,7 @@
(*
Copyright (c) 2013, Simon Cruanes
All rights reserved.
Redistribution and use in source and binary forms, with or without (* This file is free software, part of sequence. See file "license" for more details. *)
modification, are permitted provided that the following conditions are met:
Redistributions of source code must retain the above copyright notice, this (** {1 Simple and Efficient Iterators} *)
list of conditions and the following disclaimer. Redistributions in binary
form must reproduce the above copyright notice, this list of conditions and the
following disclaimer in the documentation and/or other materials provided with
the distribution.
THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND
ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE
FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR
SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY,
OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
*)
(** {1 Transient iterators, that abstract on a finite sequence of elements.} *)
(** Sequence abstract iterator type *) (** Sequence abstract iterator type *)
type 'a t = ('a -> unit) -> unit type 'a t = ('a -> unit) -> unit
@ -140,12 +118,10 @@ module MList = struct
assert (!n < Array.length a); assert (!n < Array.length a);
a.(!n) <- x; a.(!n) <- x;
incr n; incr n;
if !n = Array.length a then begin if !n = Array.length a then (
!prev := !cur; !prev := !cur;
prev := next; prev := next;
cur := Nil cur := Nil));
end
);
!prev := !cur; !prev := !cur;
!start !start
@ -272,14 +248,15 @@ let group_by (type k) ?(hash=Hashtbl.hash) ?(eq=(=)) seq =
let uniq ?(eq=fun x y -> x = y) seq k = let uniq ?(eq=fun x y -> x = y) seq k =
let has_prev = ref false let has_prev = ref false
and prev = ref (Obj.magic 0) in (* avoid option type, costly *) and prev = ref (Obj.magic 0) in (* avoid option type, costly *)
seq (fun x -> seq
(fun x ->
if !has_prev && eq !prev x if !has_prev && eq !prev x
then () (* duplicate *) then () (* duplicate *)
else begin else (
has_prev := true; has_prev := true;
prev := x; prev := x;
k x k x
end) ))
let sort_uniq (type elt) ?(cmp=Pervasives.compare) seq = let sort_uniq (type elt) ?(cmp=Pervasives.compare) seq =
let module S = Set.Make(struct let module S = Set.Make(struct
@ -290,23 +267,17 @@ let sort_uniq (type elt) ?(cmp=Pervasives.compare) seq =
fun k -> S.iter k set fun k -> S.iter k set
let product outer inner k = let product outer inner k =
outer (fun x -> outer (fun x -> inner (fun y -> k (x,y)))
inner (fun y -> k (x,y))
)
let product2 outer inner k = let product2 outer inner k =
outer (fun x -> outer (fun x -> inner (fun y -> k x y))
inner (fun y -> k x y)
)
let join ~join_row s1 s2 k = let join ~join_row s1 s2 k =
s1 (fun a -> s1 (fun a ->
s2 (fun b -> s2 (fun b ->
match join_row a b with match join_row a b with
| None -> () | None -> ()
| Some c -> k c | Some c -> k c))
)
) (* yield the combination of [a] and [b] *)
let rec unfoldr f b k = match f b with let rec unfoldr f b k = match f b with
| None -> () | None -> ()
@ -321,14 +292,16 @@ let scan f acc seq k =
let max ?(lt=fun x y -> x < y) seq = let max ?(lt=fun x y -> x < y) seq =
let ret = ref None in let ret = ref None in
seq (fun x -> match !ret with seq
(fun x -> match !ret with
| None -> ret := Some x | None -> ret := Some x
| Some y -> if lt y x then ret := Some x); | Some y -> if lt y x then ret := Some x);
!ret !ret
let min ?(lt=fun x y -> x < y) seq = let min ?(lt=fun x y -> x < y) seq =
let ret = ref None in let ret = ref None in
seq (fun x -> match !ret with seq
(fun x -> match !ret with
| None -> ret := Some x | None -> ret := Some x
| Some y -> if lt x y then ret := Some x); | Some y -> if lt x y then ret := Some x);
!ret !ret
@ -351,11 +324,11 @@ exception ExitTake
let take n seq k = let take n seq k =
let count = ref 0 in let count = ref 0 in
try try
seq (fun x -> seq
(fun x ->
if !count = n then raise ExitTake; if !count = n then raise ExitTake;
incr count; incr count;
k x; k x)
)
with ExitTake -> () with ExitTake -> ()
exception ExitTakeWhile exception ExitTakeWhile
@ -386,7 +359,8 @@ let drop n seq k =
let drop_while p seq k = let drop_while p seq k =
let drop = ref true in let drop = ref true in
seq (fun x -> seq
(fun x ->
if !drop if !drop
then if p x then () else (drop := false; k x) then if p x then () else (drop := false; k x)
else k x) else k x)
@ -418,11 +392,12 @@ exception ExitFind
let find f seq = let find f seq =
let r = ref None in let r = ref None in
begin try begin
seq (fun x -> match f x with try
seq
(fun x -> match f x with
| None -> () | None -> ()
| Some _ as res -> r := res; raise ExitFind | Some _ as res -> r := res; raise ExitFind);
);
with ExitFind -> () with ExitFind -> ()
end; end;
!r !r
@ -493,16 +468,13 @@ let to_array seq =
let n = MList.length l in let n = MList.length l in
if n = 0 if n = 0
then [||] then [||]
else begin else (
let a = Array.make n (MList.get l 0) in let a = Array.make n (MList.get l 0) in
MList.iteri (fun i x -> a.(i) <- x) l; MList.iteri (fun i x -> a.(i) <- x) l;
a a
end )
let of_array a k = let of_array a k = Array.iter k a
for i = 0 to Array.length a - 1 do
k (Array.unsafe_get a i)
done
let of_array_i a k = let of_array_i a k =
for i = 0 to Array.length a - 1 do for i = 0 to Array.length a - 1 do
@ -583,8 +555,7 @@ let of_in_channel ic =
while true do while true do
let c = input_char ic in k c let c = input_char ic in k c
done done
with End_of_file -> () with End_of_file -> ())
)
let to_buffer seq buf = let to_buffer seq buf =
seq (fun c -> Buffer.add_char buf c) seq (fun c -> Buffer.add_char buf c)
@ -745,10 +716,10 @@ let pp_seq ?(sep=", ") pp_elt formatter seq =
seq seq
(fun x -> (fun x ->
(if !first then first := false (if !first then first := false
else begin else (
Format.pp_print_string formatter sep; Format.pp_print_string formatter sep;
Format.pp_print_cut formatter (); Format.pp_print_cut formatter ();
end); ));
pp_elt formatter x) pp_elt formatter x)
let pp_buf ?(sep=", ") pp_elt buf seq = let pp_buf ?(sep=", ") pp_elt buf seq =

View file

@ -1,27 +1,5 @@
(*
copyright (c) 2013, simon cruanes
all rights reserved.
redistribution and use in source and binary forms, with or without (* This file is free software, part of sequence. See file "license" for more details. *)
modification, are permitted provided that the following conditions are met:
redistributions of source code must retain the above copyright notice, this
list of conditions and the following disclaimer. redistributions in binary
form must reproduce the above copyright notice, this list of conditions and the
following disclaimer in the documentation and/or other materials provided with
the distribution.
THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND
ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE
FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR
SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY,
OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
*)
(** {1 Simple and Efficient Iterators} *) (** {1 Simple and Efficient Iterators} *)
@ -171,8 +149,8 @@ val flatMap : ('a -> 'b t) -> 'a t -> 'b t
(** @deprecated use {!flat_map} since NEXT_RELEASE *) (** @deprecated use {!flat_map} since NEXT_RELEASE *)
val flat_map : ('a -> 'b t) -> 'a t -> 'b t val flat_map : ('a -> 'b t) -> 'a t -> 'b t
(** Monadic bind. Intuitively, it applies the function to every element of the (** Monadic bind. Intuitively, it applies the function to every
initial sequence, and calls {!concat}. element of the initial sequence, and calls {!concat}.
@since 0.5 *) @since 0.5 *)
val fmap : ('a -> 'b option) -> 'a t -> 'b t val fmap : ('a -> 'b option) -> 'a t -> 'b t

View file

@ -1,27 +1,6 @@
(*
copyright (c) 2013, simon cruanes
all rights reserved.
redistribution and use in source and binary forms, with or without (* This file is free software, part of sequence. See file "license" for more details. *)
modification, are permitted provided that the following conditions are met:
redistributions of source code must retain the above copyright notice, this
list of conditions and the following disclaimer. redistributions in binary
form must reproduce the above copyright notice, this list of conditions and the
following disclaimer in the documentation and/or other materials provided with
the distribution.
THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND
ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE
FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR
SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY,
OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
*)
(** {1 Simple and Efficient Iterators} (** {1 Simple and Efficient Iterators}
@ -143,16 +122,13 @@ val flatten : 'a t t -> 'a t
(** Alias for {!concat} *) (** Alias for {!concat} *)
val flatMap : f:('a -> 'b t) -> 'a t -> 'b t val flatMap : f:('a -> 'b t) -> 'a t -> 'b t
(** Monadic bind. Intuitively, it applies the function to every element of the (** @deprecated use {!flat_map} *)
initial sequence, and calls {!concat}.
@deprecated use {!flat_map} *)
val flat_map : f:('a -> 'b t) -> 'a t -> 'b t val flat_map : f:('a -> 'b t) -> 'a t -> 'b t
(** Alias to {!flatMap} with a more explicit name *) (** Alias to {!flatMap} with a more explicit name *)
val fmap : f:('a -> 'b option) -> 'a t -> 'b t val fmap : f:('a -> 'b option) -> 'a t -> 'b t
(** Specialized version of {!flatMap} for options. (** @deprecated use {!filter_map} *)
@deprecated use {!filter_map} *)
val filter_map : f:('a -> 'b option) -> 'a t -> 'b t val filter_map : f:('a -> 'b option) -> 'a t -> 'b t
(** Alias to {!fmap} with a more explicit name *) (** Alias to {!fmap} with a more explicit name *)