Revert "Deprecate Bigarray.*.map_file and add Unix.map_file (#997)"

This reverts commit 5ed72007f8.

GPR#997 introduced a hard dependency of Bigarray on Unix, while there
previously only was a type-level dependency. This break some programs,
such as Camomile, that linked bigarray.cma but not unix.cma.

A solution is being worked out in GPR #1077 to remove the dependency,
but I would like to go forward with opam package testing on the 4.05
branch, and getting the details right for GPR#1077 requires some care,
so I wouldn't feel comfortable rushing to merge it.

I had to handle the following conflicts:
	otherlibs/unix/unix.mli
          ("@since 4.05.0" was added in faab91a96c)
	testsuite/tests/lib-bigarray-file/mapfile.ml
          (changed by 5839c9827d9fdd55e5a9eff6bbd6173370c30bbb;
           I kept and adapted the new version)
	testsuite/tests/lib-bigarray-file/mapfile.reference
master
Gabriel Scherer 2017-03-12 12:18:09 -04:00
parent 2ad791b0b5
commit bf5a61b38c
20 changed files with 205 additions and 247 deletions

View File

@ -235,10 +235,6 @@ Next major version (4.05.0):
- GPR#996: correctly update caml_top_of_stack in systhreads
(Fabrice Le Fessant)
- GPR#997: Deprecate Bigarray.*.map_file and add Unix.map_file as a
first step towards moving Bigarray to the stdlib
(Jérémie Dimino)
### Toplevel:
- PR#7060, GPR#1035: Print exceptions in installed custom printers

View File

@ -118,7 +118,7 @@ let array_pattern_kind pat = array_type_kind pat.pat_env pat.pat_type
let bigarray_decode_type env ty tbl dfl =
match scrape env ty with
| Tconstr(Pdot(Pident mod_id, type_name, _), [], _)
when Ident.name mod_id = "CamlinternalBigarray" ->
when Ident.name mod_id = "Bigarray" ->
begin try List.assoc type_name tbl with Not_found -> dfl end
| _ ->
dfl

View File

@ -19,7 +19,33 @@ external init : unit -> unit = "caml_ba_init"
let _ = init()
include CamlinternalBigarray
type float32_elt = Float32_elt
type float64_elt = Float64_elt
type int8_signed_elt = Int8_signed_elt
type int8_unsigned_elt = Int8_unsigned_elt
type int16_signed_elt = Int16_signed_elt
type int16_unsigned_elt = Int16_unsigned_elt
type int32_elt = Int32_elt
type int64_elt = Int64_elt
type int_elt = Int_elt
type nativeint_elt = Nativeint_elt
type complex32_elt = Complex32_elt
type complex64_elt = Complex64_elt
type ('a, 'b) kind =
Float32 : (float, float32_elt) kind
| Float64 : (float, float64_elt) kind
| Int8_signed : (int, int8_signed_elt) kind
| Int8_unsigned : (int, int8_unsigned_elt) kind
| Int16_signed : (int, int16_signed_elt) kind
| Int16_unsigned : (int, int16_unsigned_elt) kind
| Int32 : (int32, int32_elt) kind
| Int64 : (int64, int64_elt) kind
| Int : (int, int_elt) kind
| Nativeint : (nativeint, nativeint_elt) kind
| Complex32 : (Complex.t, complex32_elt) kind
| Complex64 : (Complex.t, complex64_elt) kind
| Char : (char, int8_unsigned_elt) kind
(* Keep those constants in sync with the caml_ba_kind enumeration
in bigarray.h *)
@ -53,6 +79,13 @@ let kind_size_in_bytes : type a b. (a, b) kind -> int = function
| Complex64 -> 16
| Char -> 1
type c_layout = C_layout_typ
type fortran_layout = Fortran_layout_typ
type 'a layout =
C_layout: c_layout layout
| Fortran_layout: fortran_layout layout
(* Keep those constants in sync with the caml_ba_layout enumeration
in bigarray.h *)
@ -60,7 +93,7 @@ let c_layout = C_layout
let fortran_layout = Fortran_layout
module Genarray = struct
type ('a, 'b, 'c) t = ('a, 'b, 'c) genarray
type ('a, 'b, 'c) t
external create: ('a, 'b) kind -> 'c layout -> int array -> ('a, 'b, 'c) t
= "caml_ba_create"
external get: ('a, 'b, 'c) t -> int array -> 'a
@ -100,12 +133,8 @@ module Genarray = struct
external map_internal: Unix.file_descr -> ('a, 'b) kind -> 'c layout ->
bool -> int array -> int64 -> ('a, 'b, 'c) t
= "caml_ba_map_file_bytecode" "caml_ba_map_file"
let () = Unix.map_file_impl := { Unix.map_file_impl = map_internal }
let map_file fd ?pos kind layout shared dims =
try
Unix.map_file fd ?pos kind layout shared dims
with Unix.Unix_error (error, _, _) ->
raise (Sys_error (Unix.error_message error))
let map_file fd ?(pos = 0L) kind layout shared dims =
map_internal fd kind layout shared dims pos
end
module Array0 = struct

View File

@ -59,23 +59,20 @@
of abstract types for technical injectivity reasons).
*)
type float32_elt = CamlinternalBigarray.float32_elt = Float32_elt
type float64_elt = CamlinternalBigarray.float64_elt = Float64_elt
type int8_signed_elt = CamlinternalBigarray.int8_signed_elt = Int8_signed_elt
type int8_unsigned_elt = CamlinternalBigarray.int8_unsigned_elt =
Int8_unsigned_elt
type int16_signed_elt = CamlinternalBigarray.int16_signed_elt =
Int16_signed_elt
type int16_unsigned_elt = CamlinternalBigarray.int16_unsigned_elt =
Int16_unsigned_elt
type int32_elt = CamlinternalBigarray.int32_elt = Int32_elt
type int64_elt = CamlinternalBigarray.int64_elt = Int64_elt
type int_elt = CamlinternalBigarray.int_elt = Int_elt
type nativeint_elt = CamlinternalBigarray.nativeint_elt = Nativeint_elt
type complex32_elt = CamlinternalBigarray.complex32_elt = Complex32_elt
type complex64_elt = CamlinternalBigarray.complex64_elt = Complex64_elt
type float32_elt = Float32_elt
type float64_elt = Float64_elt
type int8_signed_elt = Int8_signed_elt
type int8_unsigned_elt = Int8_unsigned_elt
type int16_signed_elt = Int16_signed_elt
type int16_unsigned_elt = Int16_unsigned_elt
type int32_elt = Int32_elt
type int64_elt = Int64_elt
type int_elt = Int_elt
type nativeint_elt = Nativeint_elt
type complex32_elt = Complex32_elt
type complex64_elt = Complex64_elt
type ('a, 'b) kind = ('a, 'b) CamlinternalBigarray.kind =
type ('a, 'b) kind =
Float32 : (float, float32_elt) kind
| Float64 : (float, float64_elt) kind
| Int8_signed : (int, int8_signed_elt) kind
@ -181,11 +178,10 @@ val kind_size_in_bytes : ('a, 'b) kind -> int
(** {6 Array layouts} *)
type c_layout = CamlinternalBigarray.c_layout = C_layout_typ (**)
type c_layout = C_layout_typ (**)
(** See {!Bigarray.fortran_layout}.*)
type fortran_layout = CamlinternalBigarray.fortran_layout =
Fortran_layout_typ (**)
type fortran_layout = Fortran_layout_typ (**)
(** To facilitate interoperability with existing C and Fortran code,
this library supports two different memory layouts for big arrays,
one compatible with the C conventions,
@ -216,7 +212,7 @@ type fortran_layout = CamlinternalBigarray.fortran_layout =
re-exported as values below for backward-compatibility reasons.
*)
type 'a layout = 'a CamlinternalBigarray.layout =
type 'a layout =
C_layout: c_layout layout
| Fortran_layout: fortran_layout layout
@ -228,7 +224,7 @@ val fortran_layout : fortran_layout layout
module Genarray :
sig
type ('a, 'b, 'c) t = ('a, 'b, 'c) CamlinternalBigarray.genarray
type ('a, 'b, 'c) t
(** The type [Genarray.t] is the type of big arrays with variable
numbers of dimensions. Any number of dimensions between 0 and 16
is supported.
@ -441,10 +437,53 @@ module Genarray :
val map_file:
Unix.file_descr -> ?pos:int64 -> ('a, 'b) kind -> 'c layout ->
bool -> int array -> ('a, 'b, 'c) t
[@@ocaml.deprecated "\
Use Unix.map_file instead.\n\
Note that Bigarray.Genarray.map_file raises Sys_error while\n\
Unix.map_file raises Unix_error."]
(** Memory mapping of a file as a big array.
[Genarray.map_file fd kind layout shared dims]
returns a big array of kind [kind], layout [layout],
and dimensions as specified in [dims]. The data contained in
this big array are the contents of the file referred to by
the file descriptor [fd] (as opened previously with
[Unix.openfile], for example). The optional [pos] parameter
is the byte offset in the file of the data being mapped;
it defaults to 0 (map from the beginning of the file).
If [shared] is [true], all modifications performed on the array
are reflected in the file. This requires that [fd] be opened
with write permissions. If [shared] is [false], modifications
performed on the array are done in memory only, using
copy-on-write of the modified pages; the underlying file is not
affected.
[Genarray.map_file] is much more efficient than reading
the whole file in a big array, modifying that big array,
and writing it afterwards.
To adjust automatically the dimensions of the big array to
the actual size of the file, the major dimension (that is,
the first dimension for an array with C layout, and the last
dimension for an array with Fortran layout) can be given as
[-1]. [Genarray.map_file] then determines the major dimension
from the size of the file. The file must contain an integral
number of sub-arrays as determined by the non-major dimensions,
otherwise [Failure] is raised.
If all dimensions of the big array are given, the file size is
matched against the size of the big array. If the file is larger
than the big array, only the initial portion of the file is
mapped to the big array. If the file is smaller than the big
array, the file is automatically grown to the size of the big array.
This requires write permissions on [fd].
Array accesses are bounds-checked, but the bounds are determined by
the initial call to [map_file]. Therefore, you should make sure no
other process modifies the mapped file while you're accessing it,
or a SIGBUS signal may be raised. This happens, for instance, if the
file is shrunk.
This function raises [Sys_error] in the case of any errors from the
underlying system calls. [Invalid_argument] or [Failure] may be
raised in cases where argument validation fails. *)
end
(** {6 Zero-dimensional arrays} *)
@ -573,10 +612,8 @@ module Array1 : sig
val map_file: Unix.file_descr -> ?pos:int64 -> ('a, 'b) kind -> 'c layout ->
bool -> int -> ('a, 'b, 'c) t
[@@ocaml.deprecated "\
Use [array1_of_genarray (Unix.map_file ...)] instead.\n\
Note that Bigarray.Array1.map_file raises Sys_error while\n\
Unix.map_file raises Unix_error."]
(** Memory mapping of a file as a one-dimensional big array.
See {!Bigarray.Genarray.map_file} 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.
@ -686,10 +723,8 @@ module Array2 :
val map_file: Unix.file_descr -> ?pos:int64 -> ('a, 'b) kind -> 'c layout ->
bool -> int -> int -> ('a, 'b, 'c) t
[@@ocaml.deprecated "\
Use [array2_of_genarray (Unix.map_file ...)] instead.\n\
Note that Bigarray.Array2.map_file raises Sys_error while\n\
Unix.map_file raises Unix_error."]
(** Memory mapping of a file as a two-dimensional big array.
See {!Bigarray.Genarray.map_file} for more details. *)
external unsafe_get: ('a, 'b, 'c) t -> int -> int -> 'a
= "%caml_ba_unsafe_ref_2"
@ -822,10 +857,8 @@ module Array3 :
val map_file: Unix.file_descr -> ?pos:int64 -> ('a, 'b) kind -> 'c layout ->
bool -> int -> int -> int -> ('a, 'b, 'c) t
[@@ocaml.deprecated "\
Use [array3_of_genarray (Unix.map_file ...)] instead.\n\
Note that Bigarray.Array3.map_file raises Sys_error while\n\
Unix.map_file raises Unix_error."]
(** Memory mapping of a file as a three-dimensional big array.
See {!Bigarray.Genarray.map_file} for more details. *)
external unsafe_get: ('a, 'b, 'c) t -> int -> int -> int -> 'a
= "%caml_ba_unsafe_ref_3"

View File

@ -28,7 +28,6 @@
#include "caml/mlvalues.h"
#include "caml/sys.h"
#include "caml/signals.h"
#include "unixsupport.h"
extern int caml_ba_element_size[]; /* from bigarray_stubs.c */
@ -126,7 +125,7 @@ CAMLprim value caml_ba_map_file(value vfd, value vkind, value vlayout,
caml_enter_blocking_section();
if (fstat(fd, &st) == -1) {
caml_leave_blocking_section();
uerror("fstat", Nothing);
caml_sys_error(NO_ARG);
}
file_size = st.st_size;
/* Determine array size in bytes (or size of array without the major
@ -153,7 +152,7 @@ CAMLprim value caml_ba_map_file(value vfd, value vkind, value vlayout,
if (file_size < startpos + array_size) {
if (caml_grow_file(fd, startpos + array_size) == -1) { /* PR#5543 */
caml_leave_blocking_section();
uerror("caml_grow_file", Nothing);
caml_sys_error(NO_ARG);
}
}
}
@ -168,7 +167,7 @@ CAMLprim value caml_ba_map_file(value vfd, value vkind, value vlayout,
else
addr = NULL; /* PR#5463 - mmap fails on empty region */
caml_leave_blocking_section();
if (addr == (void *) MAP_FAILED) uerror("mmap", Nothing);
if (addr == (void *) MAP_FAILED) caml_sys_error(NO_ARG);
addr = (void *) ((uintnat) addr + delta);
/* Build and return the OCaml bigarray */
return caml_ba_alloc(flags | CAML_BA_MAPPED_FILE, num_dims, addr, dim);

View File

@ -26,6 +26,8 @@
extern int caml_ba_element_size[]; /* from bigarray_stubs.c */
static void caml_ba_sys_error(void);
#ifndef INVALID_SET_FILE_POINTER
#define INVALID_SET_FILE_POINTER (-1)
#endif
@ -72,9 +74,9 @@ CAMLprim value caml_ba_map_file(value vfd, value vkind, value vlayout,
}
/* Determine file size */
currpos = caml_ba_set_file_pointer(fd, 0, FILE_CURRENT);
if (currpos == -1) uerror("SetFilePointer", Nothing);
if (currpos == -1) caml_ba_sys_error();
file_size = caml_ba_set_file_pointer(fd, 0, FILE_END);
if (file_size == -1) uerror("SetFilePointer", Nothing);
if (file_size == -1) caml_ba_sys_error();
/* Determine array size in bytes (or size of array without the major
dimension if that dimension wasn't specified) */
array_size = caml_ba_element_size[flags & CAML_BA_KIND_MASK];
@ -103,7 +105,7 @@ CAMLprim value caml_ba_map_file(value vfd, value vkind, value vlayout,
}
li.QuadPart = startpos + array_size;
fmap = CreateFileMapping(fd, NULL, perm, li.HighPart, li.LowPart, NULL);
if (fmap == NULL) uerror("CreateFileMapping", Nothing);
if (fmap == NULL) caml_ba_sys_error();
/* Determine offset so that the mapping starts at the given file pos */
GetSystemInfo(&sysinfo);
delta = (uintnat) (startpos % sysinfo.dwAllocationGranularity);
@ -111,7 +113,7 @@ CAMLprim value caml_ba_map_file(value vfd, value vkind, value vlayout,
li.QuadPart = startpos - delta;
addr =
MapViewOfFile(fmap, mode, li.HighPart, li.LowPart, array_size + delta);
if (addr == NULL) uerror("MapViewOfFile", Nothing);;
if (addr == NULL) caml_ba_sys_error();
addr = (void *) ((uintnat) addr + delta);
/* Close the file mapping */
CloseHandle(fmap);
@ -134,3 +136,20 @@ void caml_ba_unmap_file(void * addr, uintnat len)
delta = (uintnat) addr % sysinfo.dwAllocationGranularity;
UnmapViewOfFile((void *)((uintnat)addr - delta));
}
static void caml_ba_sys_error(void)
{
char buffer[512];
DWORD errnum;
errnum = GetLastError();
if (!FormatMessage(FORMAT_MESSAGE_FROM_SYSTEM|FORMAT_MESSAGE_IGNORE_INSERTS,
NULL,
errnum,
0,
buffer,
sizeof(buffer),
NULL))
sprintf(buffer, "Unknown error %ld\n", errnum);
caml_raise_sys_error(caml_copy_string(buffer));
}

View File

@ -318,21 +318,6 @@ module LargeFile =
external fstat : file_descr -> stats = "unix_fstat_64"
end
type map_file_impl =
{ map_file_impl
: 'a 'b 'c. file_descr
-> ('a, 'b) CamlinternalBigarray.kind
-> 'c CamlinternalBigarray.layout
-> bool
-> int array
-> int64
-> ('a, 'b, 'c) CamlinternalBigarray.genarray
}
let map_file_impl =
ref { map_file_impl = fun _ _ _ _ _ _ -> failwith "Bigarray not initialized!" }
let map_file fd ?(pos=0L) kind layout shared dims =
!map_file_impl.map_file_impl fd kind layout shared dims pos
type access_permission =
R_OK
| W_OK

View File

@ -342,21 +342,6 @@ module LargeFile =
external fstat : file_descr -> stats = "unix_fstat_64"
end
type map_file_impl =
{ map_file_impl
: 'a 'b 'c. file_descr
-> ('a, 'b) CamlinternalBigarray.kind
-> 'c CamlinternalBigarray.layout
-> bool
-> int array
-> int64
-> ('a, 'b, 'c) CamlinternalBigarray.genarray
}
let map_file_impl =
ref { map_file_impl = fun _ _ _ _ _ _ -> failwith "Bigarray not initialized!" }
let map_file fd ?(pos=0L) kind layout shared dims =
!map_file_impl.map_file_impl fd kind layout shared dims pos
type access_permission =
R_OK
| W_OK

View File

@ -465,59 +465,6 @@ module LargeFile :
regular integers (type [int]), thus allowing operating on files
whose sizes are greater than [max_int]. *)
(** {6 Mapping files into memory} *)
val map_file :
file_descr -> ?pos:int64 -> ('a, 'b) CamlinternalBigarray.kind ->
'c CamlinternalBigarray.layout -> bool -> int array ->
('a, 'b, 'c) CamlinternalBigarray.genarray
(** Memory mapping of a file as a big array.
[map_file fd kind layout shared dims]
returns a big array of kind [kind], layout [layout],
and dimensions as specified in [dims]. The data contained in
this big array are the contents of the file referred to by
the file descriptor [fd] (as opened previously with
[Unix.openfile], for example). The optional [pos] parameter
is the byte offset in the file of the data being mapped;
it defaults to 0 (map from the beginning of the file).
If [shared] is [true], all modifications performed on the array
are reflected in the file. This requires that [fd] be opened
with write permissions. If [shared] is [false], modifications
performed on the array are done in memory only, using
copy-on-write of the modified pages; the underlying file is not
affected.
[Genarray.map_file] is much more efficient than reading
the whole file in a big array, modifying that big array,
and writing it afterwards.
To adjust automatically the dimensions of the big array to
the actual size of the file, the major dimension (that is,
the first dimension for an array with C layout, and the last
dimension for an array with Fortran layout) can be given as
[-1]. [Genarray.map_file] then determines the major dimension
from the size of the file. The file must contain an integral
number of sub-arrays as determined by the non-major dimensions,
otherwise [Failure] is raised.
If all dimensions of the big array are given, the file size is
matched against the size of the big array. If the file is larger
than the big array, only the initial portion of the file is
mapped to the big array. If the file is smaller than the big
array, the file is automatically grown to the size of the big array.
This requires write permissions on [fd].
Array accesses are bounds-checked, but the bounds are determined by
the initial call to [map_file]. Therefore, you should make sure no
other process modifies the mapped file while you're accessing it,
or a SIGBUS signal may be raised. This happens, for instance, if the
file is shrunk.
[Invalid_argument] or [Failure] may be raised in cases where argument
validation fails.
@since 4.05.0 *)
(** {6 Operations on file names} *)
@ -1646,16 +1593,3 @@ val setsid : unit -> int
its controlling terminal.
On Windows, not implemented. *)
(**/**)
type map_file_impl =
{ map_file_impl
: 'a 'b 'c. file_descr
-> ('a, 'b) CamlinternalBigarray.kind
-> 'c CamlinternalBigarray.layout
-> bool
-> int array
-> int64
-> ('a, 'b, 'c) CamlinternalBigarray.genarray
}
val map_file_impl : map_file_impl ref

View File

@ -294,23 +294,6 @@ module LargeFile =
external fstat : file_descr -> stats = "unix_fstat_64"
end
(* Mapping files into memory *)
type map_file_impl =
{ map_file_impl
: 'a 'b 'c. file_descr
-> ('a, 'b) CamlinternalBigarray.kind
-> 'c CamlinternalBigarray.layout
-> bool
-> int array
-> int64
-> ('a, 'b, 'c) CamlinternalBigarray.genarray
}
let map_file_impl =
ref { map_file_impl = fun _ _ _ _ _ _ -> failwith "Bigarray not initialized!" }
let map_file fd ?(pos=0L) kind layout shared dims =
!map_file_impl.map_file_impl fd kind layout shared dims pos
(* File permissions and ownership *)
type access_permission =

View File

@ -21,8 +21,6 @@ bytesLabels.cmi :
callback.cmo : obj.cmi callback.cmi
callback.cmx : obj.cmx callback.cmi
callback.cmi :
camlinternalBigarray.cmo : complex.cmi
camlinternalBigarray.cmx : complex.cmx
camlinternalFormat.cmo : sys.cmi string.cmi char.cmi \
camlinternalFormatBasics.cmi bytes.cmi buffer.cmi camlinternalFormat.cmi
camlinternalFormat.cmx : sys.cmx string.cmx char.cmx \
@ -202,8 +200,6 @@ bytesLabels.cmo : bytes.cmi bytesLabels.cmi
bytesLabels.p.cmx : bytes.cmx bytesLabels.cmi
callback.cmo : obj.cmi callback.cmi
callback.p.cmx : obj.cmx callback.cmi
camlinternalBigarray.cmo : complex.cmi
camlinternalBigarray.p.cmx : complex.cmx
camlinternalFormat.cmo : sys.cmi string.cmi char.cmi \
camlinternalFormatBasics.cmi bytes.cmi buffer.cmi camlinternalFormat.cmi
camlinternalFormat.p.cmx : sys.cmx string.cmx char.cmx \

View File

@ -48,7 +48,7 @@ OTHERS=list.cmo char.cmo uchar.cmo bytes.cmo string.cmo sys.cmo \
filename.cmo complex.cmo \
arrayLabels.cmo listLabels.cmo bytesLabels.cmo \
stringLabels.cmo moreLabels.cmo stdLabels.cmo \
spacetime.cmo camlinternalBigarray.cmo
spacetime.cmo
.PHONY: all
all: stdlib.cma std_exit.cmo camlheader target_camlheader camlheader_ur

View File

@ -1,54 +0,0 @@
(**************************************************************************)
(* *)
(* OCaml *)
(* *)
(* Manuel Serrano and Xavier Leroy, INRIA Rocquencourt *)
(* *)
(* Copyright 2000 Institut National de Recherche en Informatique et *)
(* en Automatique. *)
(* *)
(* All rights reserved. This file is distributed under the terms of *)
(* the GNU Lesser General Public License version 2.1, with the *)
(* special exception on linking described in the file LICENSE. *)
(* *)
(**************************************************************************)
(* Bigarray types. These must be kept in sync with the tables in
../bytecomp/typeopt.ml *)
type float32_elt = Float32_elt
type float64_elt = Float64_elt
type int8_signed_elt = Int8_signed_elt
type int8_unsigned_elt = Int8_unsigned_elt
type int16_signed_elt = Int16_signed_elt
type int16_unsigned_elt = Int16_unsigned_elt
type int32_elt = Int32_elt
type int64_elt = Int64_elt
type int_elt = Int_elt
type nativeint_elt = Nativeint_elt
type complex32_elt = Complex32_elt
type complex64_elt = Complex64_elt
type ('a, 'b) kind =
Float32 : (float, float32_elt) kind
| Float64 : (float, float64_elt) kind
| Int8_signed : (int, int8_signed_elt) kind
| Int8_unsigned : (int, int8_unsigned_elt) kind
| Int16_signed : (int, int16_signed_elt) kind
| Int16_unsigned : (int, int16_unsigned_elt) kind
| Int32 : (int32, int32_elt) kind
| Int64 : (int64, int64_elt) kind
| Int : (int, int_elt) kind
| Nativeint : (nativeint, nativeint_elt) kind
| Complex32 : (Complex.t, complex32_elt) kind
| Complex64 : (Complex.t, complex64_elt) kind
| Char : (char, int8_unsigned_elt) kind
type c_layout = C_layout_typ
type fortran_layout = Fortran_layout_typ
type 'a layout =
C_layout: c_layout layout
| Fortran_layout: fortran_layout layout
type ('a, 'b, 'c) genarray

View File

@ -33,14 +33,14 @@ let tests () =
Unix.openfile mapped_file
[Unix.O_RDWR; Unix.O_TRUNC; Unix.O_CREAT] 0o666 in
let a =
array1_of_genarray (Unix.map_file fd float64 c_layout true [|10000|])
array1_of_genarray (Genarray.map_file fd float64 c_layout true [|10000|])
in
Unix.close fd;
for i = 0 to 9999 do a.{i} <- float i done;
let fd = Unix.openfile mapped_file [Unix.O_RDONLY] 0 in
let b =
array2_of_genarray
(Unix.map_file fd float64 fortran_layout false [|100; -1|])
(Genarray.map_file fd float64 fortran_layout false [|100; -1|])
in
Unix.close fd;
let ok = ref true in
@ -53,7 +53,7 @@ let tests () =
b.{50,50} <- (-1.0);
let fd = Unix.openfile mapped_file [Unix.O_RDONLY] 0 in
let c =
array2_of_genarray (Unix.map_file fd float64 c_layout false [|-1; 100|])
array2_of_genarray (Genarray.map_file fd float64 c_layout false [|-1; 100|])
in
Unix.close fd;
let ok = ref true in
@ -66,7 +66,7 @@ let tests () =
let fd = Unix.openfile mapped_file [Unix.O_RDONLY] 0 in
let c =
array2_of_genarray
(Unix.map_file fd ~pos:800L float64 c_layout false [|-1; 100|])
(Genarray.map_file fd ~pos:800L float64 c_layout false [|-1; 100|])
in
Unix.close fd;
let ok = ref true in
@ -79,7 +79,7 @@ let tests () =
let fd = Unix.openfile mapped_file [Unix.O_RDONLY] 0 in
let c =
array2_of_genarray
(Unix.map_file fd ~pos:79200L float64 c_layout false [|-1; 100|])
(Genarray.map_file fd ~pos:79200L float64 c_layout false [|-1; 100|])
in
Unix.close fd;
let ok = ref true in

View File

@ -976,6 +976,61 @@ let tests () =
test_structured_io 14 (make_array3 complex64 fortran_layout 1 10 20 30
makecomplex);
testing_function "map_file";
let mapped_file = Filename.temp_file "bigarray" ".data" in
begin
let fd =
Unix.openfile mapped_file
[Unix.O_RDWR; Unix.O_TRUNC; Unix.O_CREAT] 0o666 in
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;
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;
let ok = ref true in
for i = 0 to 99 do
for j = 0 to 99 do
if b.{j+1,i+1} <> float (100 * i + j) then ok := false
done
done;
test 1 !ok true;
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;
let ok = ref true in
for i = 0 to 99 do
for j = 0 to 99 do
if c.{i,j} <> float (100 * i + j) then ok := false
done
done;
test 2 !ok true;
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;
let ok = ref true in
for i = 1 to 99 do
for j = 0 to 99 do
if c.{i-1,j} <> float (100 * i + j) then ok := false
done
done;
test 3 !ok true;
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
end;
(* 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;
()
[@@inline never]

View File

@ -75,3 +75,5 @@ reshape
output_value/input_value
1... 2... 3... 4... 5... 6... 7... 8... 9... 10... 11... 12... 13... 14...
map_file
1... 2... 3... 4...

View File

@ -20,7 +20,7 @@ CSC=$(CSC_COMMAND) $(CSC_FLAGS)
COMPFLAGS=-I $(OTOPDIR)/otherlibs/bigarray -I $(OTOPDIR)/otherlibs/dynlink \
-I $(OTOPDIR)/byterun
LD_PATH=$(TOPDIR)/otherlibs/win32unix:$(TOPDIR)/otherlibs/bigarray:$(TOPDIR)/otherlibs/dynlink
LD_PATH=$(TOPDIR)/otherlibs/bigarray:$(TOPDIR)/otherlibs/dynlink
default:
@$(SET_LD_PATH) $(MAKE) all

View File

@ -1,6 +1,5 @@
Now starting the OCaml engine.
Main is running.
Loading ../../../otherlibs/win32unix/unix.cma
Loading ../../../otherlibs/bigarray/bigarray.cma
Loading plugin.cmo
I'm the plugin.

View File

@ -5,21 +5,19 @@ let load s =
with Dynlink.Error e ->
print_endline (Dynlink.error_message e)
(* Callback must be linked to load Unix dynamically *)
let _ = Callback.register
module CamlinternalBigarray = CamlinternalBigarray
let () =
ignore (Hashtbl.hash 42.0);
print_endline "Main is running.";
Dynlink.init ();
Dynlink.allow_unsafe_modules true;
let s1,s2,s3 =
Dynlink.adapt_filename "../../../otherlibs/win32unix/unix.cma",
Dynlink.adapt_filename "../../../otherlibs/bigarray/bigarray.cma",
Dynlink.adapt_filename "plugin.cmo"
let s1,s2 =
if Dynlink.is_native then
"../../../otherlibs/bigarray/bigarray.cmxs",
"plugin.cmxs"
else
"../../../otherlibs/bigarray/bigarray.cma",
"plugin.cmo"
in
load s1;
load s2;
load s3;
print_endline "OK."

View File

@ -1,6 +1,5 @@
Now starting the OCaml engine.
Main is running.
Loading ../../../otherlibs/win32unix/unix.cmxs
Loading ../../../otherlibs/bigarray/bigarray.cmxs
Loading plugin.cmxs
I'm the plugin.