Skip to content

Commit

Permalink
Clean up lots of warnings, includes some API changes and additions
Browse files Browse the repository at this point in the history
BatInt.of_string raises Failure like stdlib.  This was documented
incorrectly.

The labeled form of List.sort was not exposed.

BatPervasives.verify was not exposed.

BatSet.partition was misspelled so the stdlib implementation was being
used.
  • Loading branch information
hcarty committed Sep 22, 2012
1 parent be8223b commit 8e29e6c
Show file tree
Hide file tree
Showing 24 changed files with 49 additions and 95 deletions.
1 change: 1 addition & 0 deletions src/batArray.mli
Original file line number Diff line number Diff line change
Expand Up @@ -318,6 +318,7 @@ end
module Labels : sig
val init : int -> f:(int -> 'a) -> 'a array
val create: int -> init:'a -> 'a array
val make: int -> init:'a -> 'a array
val make_matrix : dimx:int -> dimy:int -> 'a -> 'a array array
val create_matrix : dimx:int -> dimy:int -> 'a -> 'a array array
val sub : 'a array -> pos:int -> len:int -> 'a array
Expand Down
1 change: 0 additions & 1 deletion src/batBase64.ml
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,6 @@

exception Invalid_char
exception Invalid_table
exception Invalid_padding

external unsafe_char_of_int : int -> char = "%identity"

Expand Down
4 changes: 2 additions & 2 deletions src/batBitSet.ml
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ let print_array =
let print_bchar c =
let rc = ref c in
Buffer.clear buf;
for i = 1 to 8 do
for _i = 1 to 8 do
Buffer.add_char buf
(if !rc land 1 == 1 then '1' else '0');
rc := !rc lsr 1
Expand Down Expand Up @@ -255,7 +255,7 @@ let enum t =
let rec make n cnt =
let cur = ref n in
let cnt = ref cnt in
let rec next () =
let next () =
match next_set_bit t !cur with
Some elem ->
decr cnt;
Expand Down
4 changes: 0 additions & 4 deletions src/batBool.ml
Original file line number Diff line number Diff line change
Expand Up @@ -19,9 +19,6 @@
* Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
*)


open BatNumber

module BaseBool = struct
type t = bool
external not : bool -> bool = "%boolnot"
Expand Down Expand Up @@ -121,7 +118,6 @@ external not : bool -> bool = "%boolnot"
external ( && ) : bool -> bool -> bool = "%sequand"
external ( || ) : bool -> bool -> bool = "%sequor"

type bounded = t
let min_num, max_num = false, true

let print out t = BatInnerIO.nwrite out (to_string t)
Expand Down
2 changes: 0 additions & 2 deletions src/batBuffer.ml
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,6 @@
*)


open BatString
include Buffer

(** The underlying buffer type. *)
Expand All @@ -32,7 +31,6 @@ type buffer =
initial_buffer : string (** For resetting to the original size **)}

external buffer_of_t : t -> buffer = "%identity"
external t_of_buffer : buffer -> t = "%identity"

let print out t =
BatString.print out (contents t)
Expand Down
2 changes: 1 addition & 1 deletion src/batDynArray.ml
Original file line number Diff line number Diff line change
Expand Up @@ -252,7 +252,7 @@ let delete_last d =
iset d.arr (d.len - 1) dummy_for_gc;
changelen d (d.len - 1)

let rec blit src srcidx dst dstidx len =
let blit src srcidx dst dstidx len =
if len < 0 then invalid_arg len "blit" "len";
if srcidx < 0 || srcidx + len > src.len then invalid_arg srcidx "blit" "source index";
if dstidx < 0 || dstidx > dst.len then invalid_arg dstidx "blit" "dest index";
Expand Down
10 changes: 5 additions & 5 deletions src/batEnum.ml
Original file line number Diff line number Diff line change
Expand Up @@ -265,7 +265,7 @@ let take n e =
let r = ref [] in
begin
try
for i = 1 to n do
for _i = 1 to n do
r := e.next () :: !r
done
with No_more_elements -> ()
Expand Down Expand Up @@ -419,7 +419,7 @@ let for_all f t =
with No_more_elements -> true

(* test paired elements, ignore any extra elements from one enum *)
let for_all2 f t1 t2 =
let _for_all2 f t1 t2 =
try
let rec aux () = f (t1.next()) (t2.next()) && aux () in
aux ()
Expand Down Expand Up @@ -701,7 +701,7 @@ let range ?until x =


let drop n e =
for i = 1 to n do
for _i = 1 to n do
junk e
done

Expand Down Expand Up @@ -891,7 +891,7 @@ let clump clump_size add get e = (* convert a uchar enum into a ustring enum *)
| Some x ->
add x;
(try
for i = 2 to clump_size do
for _i = 2 to clump_size do
add (e.next ())
done
with No_more_elements -> ());
Expand Down Expand Up @@ -1196,7 +1196,7 @@ module Incubator = struct
else if y > x then Lt
else Eq

let eq_elements eq_elt a1 a2 = for_all2 eq_elt a1 a2
let eq_elements eq_elt a1 a2 = _for_all2 eq_elt a1 a2

let rec ord_elements ord_elt t u =
match (get t, get u) with
Expand Down
6 changes: 3 additions & 3 deletions src/batFingerTree.ml
Original file line number Diff line number Diff line change
Expand Up @@ -185,10 +185,10 @@ struct
let dummy_printer f _ =
Format.pp_print_string f "_"

let pp_debug ?(pp_measure = dummy_printer) pp_a f t =
let _pp_debug ?(pp_measure = dummy_printer) pp_a f t =
pp_debug_tree pp_measure pp_a f t

let pp_list pp_a f = function
let _pp_list pp_a f = function
| [] -> Format.fprintf f "[]"
| h :: t ->
Format.fprintf f "[%a" pp_a h;
Expand Down Expand Up @@ -416,7 +416,7 @@ struct
| [a; b; c] -> three ~monoid ~measure a b c
| [a; b; c; d] -> four ~monoid ~measure a b c d
| _ -> assert false (*BISECT-VISIT*)
let to_digit_list_node ~monoid = function
let _to_digit_list_node ~monoid = function
| [a] -> one_node a
| [a; b] -> two_node ~monoid a b
| [a; b; c] -> three_node ~monoid a b c
Expand Down
5 changes: 0 additions & 5 deletions src/batFloat.ml
Original file line number Diff line number Diff line change
Expand Up @@ -145,16 +145,12 @@ external modulo : float -> float -> float = "caml_fmod_float" "fmod" "float"
external pow : float -> float -> float = "caml_power_float" "pow" "float"
external of_int : int -> float = "%floatofint"
external to_int : float -> int = "%intoffloat"
external of_float : float -> float = "%identity"
external to_float : float -> float = "%identity"
external ( + ) : t -> t -> t = "%addfloat"
external ( - ) : t -> t -> t = "%subfloat"
external ( * ) : t -> t -> t = "%mulfloat"
external ( / ) : t -> t -> t = "%divfloat"
external ( ** ) : t -> t -> t = "caml_power_float" "pow" "float"


type bounded = t
let min_num, max_num = neg_infinity, infinity

type fpkind = Pervasives.fpclass =
Expand Down Expand Up @@ -289,7 +285,6 @@ module Safe_float = struct
let frexp x = let (f, _) as result = frexp x in if_safe f; result (*BISECT-VISIT*)
let ldexp = safe2 ldexp

type bounded = t
let min_num, max_num = neg_infinity, infinity

type fpkind = Pervasives.fpclass =
Expand Down
3 changes: 0 additions & 3 deletions src/batGlobal.ml
Original file line number Diff line number Diff line change
Expand Up @@ -44,8 +44,5 @@ let undef (r, _) =
let isdef (r, _) =
!r <> None

let opt (r, _) =
!r

let get (r,_) = !r
(*BISECT-IGNORE-END*)
5 changes: 2 additions & 3 deletions src/batHashtbl.ml
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,6 @@
let replace = Hashtbl.replace
let iter = Hashtbl.iter
let fold = Hashtbl.fold
let length = Hashtbl.length
let hash = Hashtbl.hash
external hash_param : int -> int -> 'a -> int = "caml_hash_univ_param" "noalloc"

Expand All @@ -54,7 +53,7 @@
external h_conv : ('a, 'b) t -> ('a, 'b) h_t = "%identity"
external h_make : ('a, 'b) h_t -> ('a, 'b) t = "%identity"

let resize hashfun tbl =
let _resize hashfun tbl =
let odata = tbl.data in
let osize = Array.length odata in
let nsize = min (2 * osize + 1) Sys.max_array_length in
Expand Down Expand Up @@ -511,11 +510,11 @@
let add e ~key ~data = add e key data
let replace e ~key ~data = replace e key data
let iter ~f e = iter (label f) e
let fold ~f e ~init = fold (label f) e init
let map ~f e = map (label f) e
let filter ~f e = filter f e
let filteri ~f e = filteri (label f) e
let filter_map ~f e = filter_map (label f) e
let fold ~f e ~init = fold (label f) e init
end

module Exceptionless =
Expand Down
4 changes: 0 additions & 4 deletions src/batInt.ml
Original file line number Diff line number Diff line change
Expand Up @@ -94,10 +94,6 @@ module BaseInt = struct
external of_int : int -> int = "%identity"
external to_int : int -> int = "%identity"


let of_string x =
try int_of_string x
with Failure "int_of_string" -> raise (Invalid_argument "int_of_string")
let to_string = string_of_int

let enum = enum
Expand Down
4 changes: 2 additions & 2 deletions src/batInt.mli
Original file line number Diff line number Diff line change
Expand Up @@ -136,7 +136,7 @@ val of_string : string -> int
The string is read in decimal (by default) or in hexadecimal,
octal or binary if the string begins with [0x], [0o] or [0b]
respectively.
Raise [Invalid_argument] if the given string is not
Raise [Failure] if the given string is not
a valid representation of an integer, or if the integer represented
exceeds the range of integers representable in type [int]. *)

Expand Down Expand Up @@ -342,7 +342,7 @@ module Safe_int : sig
The string is read in decimal (by default) or in hexadecimal,
octal or binary if the string begins with [0x], [0o] or [0b]
respectively.
Raise [Invalid_argument] if the given string is not
Raise [Failure] if the given string is not
a valid representation of an integer, or if the integer represented
exceeds the range of integers representable in type [int]. *)

Expand Down
4 changes: 0 additions & 4 deletions src/batInt32.ml
Original file line number Diff line number Diff line change
Expand Up @@ -115,10 +115,6 @@ external bits_of_float : float -> int32 = "caml_int32_bits_of_float"
external float_of_bits : int32 -> float = "caml_int32_float_of_bits"
external format : string -> int32 -> string = "caml_int32_format"




type bounded = t
let min_num, max_num = min_int, max_int

let print out t = BatInnerIO.nwrite out (to_string t)
Expand Down
23 changes: 10 additions & 13 deletions src/batList.ml
Original file line number Diff line number Diff line change
Expand Up @@ -106,7 +106,7 @@ let append l1 l2 =
loop r t;
inj r

let rec flatten l =
let flatten l =
let rec inner dst = function
| [] -> dst
| h :: t ->
Expand Down Expand Up @@ -241,7 +241,7 @@ let interleave ?first ?last (sep:'a) (l:'a list) =
(interleave ~first:(-1) ~last:(-2) 0 []) [-1;-2]
*)

let rec unique ?(eq = ( = )) l =
let unique ?(eq = ( = )) l =
let rec loop dst = function
| [] -> ()
| h :: t ->
Expand Down Expand Up @@ -451,36 +451,36 @@ let find_all p l =
findnext dummy l;
dummy.tl

let rec findi p l =
let findi p l =
let rec loop n = function
| [] -> raise Not_found
| h :: t ->
if p n h then (n,h) else loop (n+1) t
in
loop 0 l

let rec index_of e l =
let index_of e l =
let rec loop n = function
| [] -> None
| h::_ when h = e -> Some n
| _::t -> loop ( n + 1 ) t
in loop 0 l

let rec index_ofq e l =
let index_ofq e l =
let rec loop n = function
| [] -> None
| h::_ when h == e -> Some n
| _::t -> loop ( n + 1 ) t
in loop 0 l

let rec rindex_of e l =
let rindex_of e l =
let rec loop n acc = function
| [] -> acc
| h::t when h = e -> loop ( n + 1) ( Some n ) t
| _::t -> loop ( n + 1 ) acc t
in loop 0 None l

let rec rindex_ofq e l =
let rindex_ofq e l =
let rec loop n acc = function
| [] -> acc
| h::t when h == e -> loop ( n + 1) ( Some n ) t
Expand Down Expand Up @@ -542,7 +542,7 @@ let combine l1 l2 =
loop dummy l1 l2;
dummy.tl

let rec init size f =
let init size f =
if size = 0 then []
else if size < 0 then invalid_arg "BatList.init"
else
Expand Down Expand Up @@ -635,7 +635,7 @@ let remove l x =
loop dummy l;
dummy.tl

let rec remove_if f lst =
let remove_if f lst =
let rec loop dst = function
| [] -> ()
| x :: l ->
Expand All @@ -650,7 +650,7 @@ let rec remove_if f lst =
loop dummy lst;
dummy.tl

let rec remove_all l x =
let remove_all l x =
let rec loop dst = function
| [] -> ()
| h :: t ->
Expand Down Expand Up @@ -865,10 +865,7 @@ end


module Labels = struct

type 'a t = 'a list
let init i ~f = init i f
let make n x = make n x
let iteri ~f l = iteri f l
let map ~f l = map f l
let mapi ~f l = mapi f l
Expand Down
1 change: 1 addition & 0 deletions src/batList.mli
Original file line number Diff line number Diff line change
Expand Up @@ -733,6 +733,7 @@ module Labels : sig
val drop_while : f:('a -> bool) -> 'a list -> 'a list
val stable_sort : ?cmp:('a -> 'a -> int) -> 'a list -> 'a list
val fast_sort : ?cmp:('a -> 'a -> int) -> 'a list -> 'a list
val sort : ?cmp:('a -> 'a -> int) -> 'a list -> 'a list
val merge : ?cmp:('a -> 'a -> int) -> 'a list -> 'a list -> 'a list
module LExceptionless : sig
val find : f:('a -> bool) -> 'a list -> 'a option
Expand Down
Loading

0 comments on commit 8e29e6c

Please sign in to comment.