Skip to content

Commit

Permalink
Remove the 'dispose' functions from Bigarray.
Browse files Browse the repository at this point in the history
(Partial revert of commit 12326, keeping the other good bits.)


git-svn-id: http://caml.inria.fr/svn/ocaml/version/4.00@12433 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
  • Loading branch information
xavierleroy committed May 6, 2012
1 parent 5833a04 commit 5ca6abd
Show file tree
Hide file tree
Showing 6 changed files with 20 additions and 115 deletions.
4 changes: 0 additions & 4 deletions Changes
Expand Up @@ -64,10 +64,6 @@ Standard library:
- Set and Map: more efficient implementation of "filter" and "partition"
- String: new function "map" (PR#3888)

Other libraries:
- Bigarray: added "release" functions that free memory and file mappings
just like GC finalization does eventually, but does it immediately.

Bug Fixes:
- PR#1643: functions of the Lazy module whose named started with 'lazy_' have
been deprecated, and new ones without the prefix added
Expand Down
8 changes: 0 additions & 8 deletions otherlibs/bigarray/bigarray.ml
Expand Up @@ -99,8 +99,6 @@ module Genarray = struct
= "caml_ba_map_file_bytecode" "caml_ba_map_file"
let map_file fd ?(pos = 0L) kind layout shared dims =
map_internal fd kind layout shared dims pos
external release: ('a, 'b, 'c) t -> unit
= "caml_ba_release"
end

module Array1 = struct
Expand All @@ -124,8 +122,6 @@ module Array1 = struct
ba
let map_file fd ?pos kind layout shared dim =
Genarray.map_file fd ?pos kind layout shared [|dim|]
external release: ('a, 'b, 'c) t -> unit
= "caml_ba_release"
end

module Array2 = struct
Expand Down Expand Up @@ -165,8 +161,6 @@ module Array2 = struct
ba
let map_file fd ?pos kind layout shared dim1 dim2 =
Genarray.map_file fd ?pos kind layout shared [|dim1;dim2|]
external release: ('a, 'b, 'c) t -> unit
= "caml_ba_release"
end

module Array3 = struct
Expand Down Expand Up @@ -216,8 +210,6 @@ module Array3 = struct
ba
let map_file fd ?pos kind layout shared dim1 dim2 dim3 =
Genarray.map_file fd ?pos kind layout shared [|dim1;dim2;dim3|]
external release: ('a, 'b, 'c) t -> unit
= "caml_ba_release"
end

external genarray_of_array1: ('a, 'b, 'c) Array1.t -> ('a, 'b, 'c) Genarray.t
Expand Down
58 changes: 11 additions & 47 deletions otherlibs/bigarray/bigarray.mli
Expand Up @@ -426,27 +426,7 @@ module Genarray :
or a SIGBUS signal may be raised. This happens, for instance, if the
file is shrinked. *)

val release: ('a, 'b, 'c) t -> unit
(** Release the resources associated with the given big array,
then set all of its dimensions to 0, causing subsequent accesses
to the big array to fail. This releasing of resources is performed
automatically by the garbage collector when the big array is no longer
referenced by the program. However, memory behavior of the program
can be improved by releasing the resources explicitly via
[Genarray.release] as soon as the big array is no longer useful.
If the big array was created with [Genarray.create], the memory
space occupied by its data is freed. If the big array was
created with [Genarray.map_file], updates performed on the array
are flushed to the file (if the mapping is shared), then the
mapping is removed, freeing the corresponding virtual memory
space. If several views on the big array data were created
using [Genarray.sub_*] or [Genarray.slice_*], data release occurs
when the last not-yet-released view is released. Multiple calls
to [Genarray.release] on the same big array are safe: the second
and subsequent calls have no effect. *)

end
end

(** {6 One-dimensional arrays} *)

Expand Down Expand Up @@ -516,20 +496,16 @@ module Array1 : sig
(** Memory mapping of a file as a one-dimensional big array.
See {!Bigarray.Genarray.map_file} for more details. *)

val release: ('a, 'b, 'c) t -> unit
(** Explicit release of the resources associated with the big array.
See {!Bigarray.Genarray.release} for more details. *)

external unsafe_get: ('a, 'b, 'c) t -> int -> 'a = "%caml_ba_unsafe_ref_1"
(** Like {!Bigarray.Array1.get}, but bounds checking is not always performed.
Use with caution and only when the program logic guarantees that
the access is within bounds and the big array has not been released. *)
the access is within bounds. *)

external unsafe_set: ('a, 'b, 'c) t -> int -> 'a -> unit
= "%caml_ba_unsafe_set_1"
(** Like {!Bigarray.Array1.set}, but bounds checking is not always performed.
Use with caution and only when the program logic guarantees that
the access is within bounds and the big array has not been released. *)
the access is within bounds. *)

end

Expand Down Expand Up @@ -625,21 +601,15 @@ module Array2 :
(** Memory mapping of a file as a two-dimensional big array.
See {!Bigarray.Genarray.map_file} for more details. *)

val release: ('a, 'b, 'c) t -> unit
(** Explicit release of the resources associated with the big array.
See {!Bigarray.Genarray.release} for more details. *)

external unsafe_get: ('a, 'b, 'c) t -> int -> int -> 'a
= "%caml_ba_unsafe_ref_2"
(** Like {!Bigarray.Array2.get}, but bounds checking is not always performed.
Use with caution and only when the program logic guarantees that
the access is within bounds and the big array has not been released. *)
(** Like {!Bigarray.Array2.get}, but bounds checking is not always
performed. *)

external unsafe_set: ('a, 'b, 'c) t -> int -> int -> 'a -> unit
= "%caml_ba_unsafe_set_2"
(** Like {!Bigarray.Array2.set}, but bounds checking is not always performed.
Use with caution and only when the program logic guarantees that
the access is within bounds and the big array has not been released. *)
(** Like {!Bigarray.Array2.set}, but bounds checking is not always
performed. *)

end

Expand Down Expand Up @@ -759,21 +729,15 @@ module Array3 :
(** Memory mapping of a file as a three-dimensional big array.
See {!Bigarray.Genarray.map_file} for more details. *)

val release: ('a, 'b, 'c) t -> unit
(** Explicit release of the resources associated with the big array.
See {!Bigarray.Genarray.release} for more details. *)

external unsafe_get: ('a, 'b, 'c) t -> int -> int -> int -> 'a
= "%caml_ba_unsafe_ref_3"
(** Like {!Bigarray.Array3.get}, but bounds checking is not always performed.
Use with caution and only when the program logic guarantees that
the access is within bounds and the big array has not been released. *)
(** Like {!Bigarray.Array3.get}, but bounds checking is not always
performed. *)

external unsafe_set: ('a, 'b, 'c) t -> int -> int -> int -> 'a -> unit
= "%caml_ba_unsafe_set_3"
(** Like {!Bigarray.Array3.set}, but bounds checking is not always performed.
Use with caution and only when the program logic guarantees that
the access is within bounds and the big array has not been released. *)
(** Like {!Bigarray.Array3.set}, but bounds checking is not always
performed. *)

end

Expand Down
16 changes: 2 additions & 14 deletions otherlibs/bigarray/bigarray_stubs.c
Expand Up @@ -496,19 +496,18 @@ CAMLprim value caml_ba_layout(value vb)
return Val_int(Caml_ba_array_val(vb)->flags & CAML_BA_LAYOUT_MASK);
}

/* Finalization / release of a big array */
/* Finalization of a big array */

static void caml_ba_finalize(value v)
{
struct caml_ba_array * b = Caml_ba_array_val(v);
intnat i;

switch (b->flags & CAML_BA_MANAGED_MASK) {
case CAML_BA_EXTERNAL:
break;
case CAML_BA_MANAGED:
if (b->proxy == NULL) {
free(b->data); /* no op if b->data = NULL */
free(b->data);
} else {
if (-- b->proxy->refcount == 0) {
free(b->proxy->data);
Expand All @@ -527,17 +526,6 @@ static void caml_ba_finalize(value v)
}
break;
}
/* Make sure that subsequent accesses to the bigarray fail (empty bounds)
and that subsequent calls to caml_ba_finalize do nothing. */
for (i = 0; i < b->num_dims; i++) b->dim[i] = 0;
b->data = NULL;
b->proxy = NULL;
}

CAMLprim value caml_ba_release(value v)
{
caml_ba_finalize(v);
return Val_unit;
}

/* Comparison of two big arrays */
Expand Down
41 changes: 6 additions & 35 deletions testsuite/tests/lib-bigarray/bigarrays.ml
Expand Up @@ -384,12 +384,6 @@ let _ =
test 12 true (test_blit_fill complex64 [Complex.zero; Complex.one; Complex.i]
Complex.i 1 1);

testing_function "release";
let a = from_list int [1;2;3;4;5] in
test 1 (Array1.dim a) 5;
Array1.release a;
test 2 (Array1.dim a) 0;

(* Bi-dimensional arrays *)

print_newline();
Expand Down Expand Up @@ -539,14 +533,6 @@ let _ =
test 7 (Array2.slice_right a 2) (from_list_fortran int [1002;2002;3002;4002;5002]);
test 8 (Array2.slice_right a 3) (from_list_fortran int [1003;2003;3003;4003;5003]);

testing_function "release";
let a = (make_array2 int c_layout 0 4 6 id) in
test 1 (Array2.dim1 a) 4;
test 2 (Array2.dim2 a) 6;
Array2.release a;
test 3 (Array2.dim1 a) 0;
test 4 (Array2.dim2 a) 0;

(* Tri-dimensional arrays *)

print_newline();
Expand Down Expand Up @@ -668,16 +654,6 @@ let _ =
test 6 (Array3.slice_right_1 a 1 2) (from_list_fortran int [112;212;312]);
test 7 (Array3.slice_right_1 a 3 1) (from_list_fortran int [131;231;331]);

testing_function "release";
let a = (make_array3 int c_layout 0 4 5 6 id) in
test 1 (Array3.dim1 a) 4;
test 2 (Array3.dim2 a) 5;
test 3 (Array3.dim3 a) 6;
Array3.release a;
test 4 (Array3.dim1 a) 0;
test 5 (Array3.dim2 a) 0;
test 6 (Array3.dim3 a) 0;

(* Reshaping *)
print_newline();
testing_function "------ Reshaping --------";
Expand Down Expand Up @@ -741,7 +717,6 @@ let _ =
let a = Array1.map_file fd float64 c_layout true 10000 in
Unix.close fd;
for i = 0 to 9999 do a.{i} <- float i done;
Array1.release a;
let fd = Unix.openfile mapped_file [Unix.O_RDONLY] 0 in
let b = Array2.map_file fd float64 fortran_layout false 100 (-1) in
Unix.close fd;
Expand All @@ -752,8 +727,7 @@ let _ =
done
done;
test 1 !ok true;
b.{50,50} <- (-1.0); (* private mapping -> no effect on file *)
Array2.release b;
b.{50,50} <- (-1.0);
let fd = Unix.openfile mapped_file [Unix.O_RDONLY] 0 in
let c = Array2.map_file fd float64 c_layout false (-1) 100 in
Unix.close fd;
Expand All @@ -764,7 +738,6 @@ let _ =
done
done;
test 2 !ok true;
Array2.release c;
let fd = Unix.openfile mapped_file [Unix.O_RDONLY] 0 in
let c = Array2.map_file fd ~pos:800L float64 c_layout false (-1) 100 in
Unix.close fd;
Expand All @@ -775,21 +748,19 @@ let _ =
done
done;
test 3 !ok true;
Array2.release c;
let fd = Unix.openfile mapped_file [Unix.O_RDONLY] 0 in
let c = Array2.map_file fd ~pos:79200L float64 c_layout false (-1) 100 in
Unix.close fd;
let ok = ref true in
for j = 0 to 99 do
if c.{0,j} <> float (100 * 99 + j) then ok := false
done;
test 4 !ok true;
Array2.release c;
test 5 (Array2.dim1 c) 0;
test 5 (Array2.dim2 c) 0
test 4 !ok true
end;
(* Win32 doesn't let us erase the file if any mapping on the file is
still active. Normally, they have all been released explicitly. *)
(* Force garbage collection of the mapped bigarrays above, otherwise
Win32 doesn't let us erase the file. Notice the begin...end above
so that the VM doesn't keep stack references to the mapped bigarrays. *)
Gc.full_major();
Sys.remove mapped_file;

()
Expand Down
8 changes: 1 addition & 7 deletions testsuite/tests/lib-bigarray/bigarrays.reference
Expand Up @@ -17,8 +17,6 @@ sub
1... 2... 3... 4... 5... 6... 7... 8... 9...
blit, fill
1... 2... 3... 4... 5... 6... 7... 8... 9... 10... 11... 12...
release
1... 2...

------ Array2 --------

Expand All @@ -34,8 +32,6 @@ sub
1... 2...
slice
1... 2... 3... 4... 5... 6... 7... 8...
release
1... 2... 3... 4...

------ Array3 --------

Expand All @@ -49,8 +45,6 @@ dim
1... 2... 3... 4... 5... 6...
slice1
1... 2... 3... 4... 5... 6... 7...
release
1... 2... 3... 4... 5... 6...

------ Reshaping --------

Expand All @@ -64,4 +58,4 @@ reshape_2
output_value/input_value
1... 2... 3... 4... 5... 6... 7... 8... 9... 10... 11... 12... 13... 14...
map_file
1... 2... 3... 4... 5... 5...
1... 2... 3... 4...

0 comments on commit 5ca6abd

Please sign in to comment.