~ubuntu-branches/debian/sid/ocaml/sid

« back to all changes in this revision

Viewing changes to otherlibs/bigarray/bigarray.mli

  • Committer: Bazaar Package Importer
  • Author(s): Stefano Zacchiroli
  • Date: 2009-02-22 08:49:13 UTC
  • mfrom: (12.1.1 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090222084913-3i0uw2bhd0lgw0ok
* Uploading to unstable
* debian/control: bump dh-ocaml to (>= 0.4) to avoid buggy ocamlinit.mk

Show diffs side-by-side

added added

removed removed

Lines of Context:
11
11
(*                                                                     *)
12
12
(***********************************************************************)
13
13
 
14
 
(* $Id: bigarray.mli,v 1.25 2007/02/21 15:16:53 xleroy Exp $ *)
 
14
(* $Id: bigarray.mli,v 1.27.2.1 2008/10/08 13:07:13 doligez Exp $ *)
15
15
 
16
16
(** Large, multi-dimensional, numerical arrays.
17
17
 
227
227
     Big arrays returned by [Genarray.create] are not initialized:
228
228
     the initial values of array elements is unspecified.
229
229
 
230
 
     [Genarray.create] raises [Invalid_arg] if the number of dimensions
 
230
     [Genarray.create] raises [Invalid_argument] if the number of dimensions
231
231
     is not in the range 1 to 16 inclusive, or if one of the dimensions
232
232
     is negative. *)
233
233
 
243
243
     big array [a].  The first dimension corresponds to [n = 0];
244
244
     the second dimension corresponds to [n = 1]; the last dimension,
245
245
     to [n = Genarray.num_dims a - 1].
246
 
     Raise [Invalid_arg] if [n] is less than 0 or greater or equal than
 
246
     Raise [Invalid_argument] if [n] is less than 0 or greater or equal than
247
247
     [Genarray.num_dims a]. *)
248
248
 
249
249
  external kind: ('a, 'b, 'c) t -> ('a, 'b) kind = "caml_ba_kind"
262
262
     and strictly less than the corresponding dimensions of [a].
263
263
     If [a] has Fortran layout, the coordinates must be greater or equal
264
264
     than 1 and less or equal than the corresponding dimensions of [a].
265
 
     Raise [Invalid_arg] if the array [a] does not have exactly [N]
 
265
     Raise [Invalid_argument] if the array [a] does not have exactly [N]
266
266
     dimensions, or if the coordinates are outside the array bounds.
267
267
 
268
268
     If [N > 3], alternate syntax is provided: you can write
280
280
 
281
281
     The array [a] must have exactly [N] dimensions, and all coordinates
282
282
     must lie inside the array bounds, as described for [Genarray.get];
283
 
     otherwise, [Invalid_arg] is raised.
 
283
     otherwise, [Invalid_argument] is raised.
284
284
 
285
285
     If [N > 3], alternate syntax is provided: you can write
286
286
     [a.{i1, i2, ..., iN} <- v] instead of
304
304
     array [a].
305
305
 
306
306
     [Genarray.sub_left] applies only to big arrays in C layout.
307
 
     Raise [Invalid_arg] if [ofs] and [len] do not designate
 
307
     Raise [Invalid_argument] if [ofs] and [len] do not designate
308
308
     a valid sub-array of [a], that is, if [ofs < 0], or [len < 0],
309
309
     or [ofs + len > Genarray.nth_dim a 0]. *)
310
310
 
324
324
     array [a].
325
325
 
326
326
     [Genarray.sub_right] applies only to big arrays in Fortran layout.
327
 
     Raise [Invalid_arg] if [ofs] and [len] do not designate
 
327
     Raise [Invalid_argument] if [ofs] and [len] do not designate
328
328
     a valid sub-array of [a], that is, if [ofs < 1], or [len < 0],
329
329
     or [ofs + len > Genarray.nth_dim a (Genarray.num_dims a - 1)]. *)
330
330
 
343
343
     the original array share the same storage space.
344
344
 
345
345
     [Genarray.slice_left] applies only to big arrays in C layout.
346
 
     Raise [Invalid_arg] if [M >= N], or if [[|i1; ... ; iM|]]
 
346
     Raise [Invalid_argument] if [M >= N], or if [[|i1; ... ; iM|]]
347
347
     is outside the bounds of [a]. *)
348
348
 
349
349
  external slice_right:
361
361
     the original array share the same storage space.
362
362
 
363
363
     [Genarray.slice_right] applies only to big arrays in Fortran layout.
364
 
     Raise [Invalid_arg] if [M >= N], or if [[|i1; ... ; iM|]]
 
364
     Raise [Invalid_argument] if [M >= N], or if [[|i1; ... ; iM|]]
365
365
     is outside the bounds of [a]. *)
366
366
 
367
367
  external blit: ('a, 'b, 'c) t -> ('a, 'b, 'c) t -> unit
391
391
     the file descriptor [fd] (as opened previously with
392
392
     [Unix.openfile], for example).  The optional [pos] parameter
393
393
     is the byte offset in the file of the data being mapped;
394
 
     it default to 0 (map from the beginning of the file).
 
394
     it defaults to 0 (map from the beginning of the file).
395
395
 
396
396
     If [shared] is [true], all modifications performed on the array
397
397
     are reflected in the file.  This requires that [fd] be opened
458
458
     [x] must be greater or equal than [0] and strictly less than
459
459
     [Array1.dim a] if [a] has C layout.  If [a] has Fortran layout,
460
460
     [x] must be greater or equal than [1] and less or equal than
461
 
     [Array1.dim a].  Otherwise, [Invalid_arg] is raised. *)
 
461
     [Array1.dim a].  Otherwise, [Invalid_argument] is raised. *)
462
462
 
463
463
  external set: ('a, 'b, 'c) t -> int -> 'a -> unit = "%caml_ba_set_1"
464
464
  (** [Array1.set a x v], also written [a.{x} <- v],
465
465
     stores the value [v] at index [x] in [a].
466
466
     [x] must be inside the bounds of [a] as described in
467
467
     {!Bigarray.Array1.get};
468
 
     otherwise, [Invalid_arg] is raised. *)
 
468
     otherwise, [Invalid_argument] is raised. *)
469
469
 
470
470
  external sub: ('a, 'b, 'c) t -> int -> int -> ('a, 'b, 'c) t
471
471
      = "caml_ba_sub"
489
489
    bool -> int -> ('a, 'b, 'c) t
490
490
  (** Memory mapping of a file as a one-dimensional big array.
491
491
     See {!Bigarray.Genarray.map_file} for more details. *)
 
492
 
 
493
  external unsafe_get: ('a, 'b, 'c) t -> int -> 'a = "%caml_ba_unsafe_ref_1"
 
494
  (** Like {!Bigarray.Array1.get}, but bounds checking is not always performed.
 
495
      Use with caution and only when the program logic guarantees that
 
496
      the access is within bounds. *)
 
497
 
 
498
  external unsafe_set: ('a, 'b, 'c) t -> int -> 'a -> unit
 
499
                     = "%caml_ba_unsafe_set_1"
 
500
  (** Like {!Bigarray.Array1.set}, but bounds checking is not always performed.
 
501
      Use with caution and only when the program logic guarantees that
 
502
      the access is within bounds. *)
 
503
 
492
504
end
493
505
 
494
506
 
527
539
     returns the element of [a] at coordinates ([x], [y]).
528
540
     [x] and [y] must be within the bounds
529
541
     of [a], as described for {!Bigarray.Genarray.get};
530
 
     otherwise, [Invalid_arg] is raised. *)
 
542
     otherwise, [Invalid_argument] is raised. *)
531
543
 
532
544
  external set: ('a, 'b, 'c) t -> int -> int -> 'a -> unit = "%caml_ba_set_2"
533
545
  (** [Array2.set a x y v], or alternatively [a.{x,y} <- v],
534
546
     stores the value [v] at coordinates ([x], [y]) in [a].
535
547
     [x] and [y] must be within the bounds of [a],
536
548
     as described for {!Bigarray.Genarray.set};
537
 
     otherwise, [Invalid_arg] is raised. *)
 
549
     otherwise, [Invalid_argument] is raised. *)
538
550
 
539
551
  external sub_left: ('a, 'b, c_layout) t -> int -> int -> ('a, 'b, c_layout) t
540
552
    = "caml_ba_sub"
583
595
  (** Memory mapping of a file as a two-dimensional big array.
584
596
     See {!Bigarray.Genarray.map_file} for more details. *)
585
597
 
586
 
  end
 
598
  external unsafe_get: ('a, 'b, 'c) t -> int -> int -> 'a
 
599
                     = "%caml_ba_unsafe_ref_2"
 
600
  (** Like {!Bigarray.Array2.get}, but bounds checking is not always
 
601
      performed. *)
 
602
 
 
603
  external unsafe_set: ('a, 'b, 'c) t -> int -> int -> 'a -> unit
 
604
                     = "%caml_ba_unsafe_set_2"
 
605
  (** Like {!Bigarray.Array2.set}, but bounds checking is not always
 
606
      performed. *)
 
607
 
 
608
end
587
609
 
588
610
(** {6 Three-dimensional arrays} *)
589
611
 
623
645
     returns the element of [a] at coordinates ([x], [y], [z]).
624
646
     [x], [y] and [z] must be within the bounds of [a],
625
647
     as described for {!Bigarray.Genarray.get};
626
 
     otherwise, [Invalid_arg] is raised. *)
 
648
     otherwise, [Invalid_argument] is raised. *)
627
649
 
628
650
  external set: ('a, 'b, 'c) t -> int -> int -> int -> 'a -> unit
629
651
    = "%caml_ba_set_3"
631
653
     stores the value [v] at coordinates ([x], [y], [z]) in [a].
632
654
     [x], [y] and [z] must be within the bounds of [a],
633
655
     as described for {!Bigarray.Genarray.set};
634
 
     otherwise, [Invalid_arg] is raised. *)
 
656
     otherwise, [Invalid_argument] is raised. *)
635
657
 
636
658
  external sub_left: ('a, 'b, c_layout) t -> int -> int -> ('a, 'b, c_layout) t
637
659
    = "caml_ba_sub"
700
722
             bool -> int -> int -> int -> ('a, 'b, 'c) t
701
723
  (** Memory mapping of a file as a three-dimensional big array.
702
724
     See {!Bigarray.Genarray.map_file} for more details. *)
703
 
  end
 
725
 
 
726
  external unsafe_get: ('a, 'b, 'c) t -> int -> int -> int -> 'a
 
727
                     = "%caml_ba_unsafe_ref_3"
 
728
  (** Like {!Bigarray.Array3.get}, but bounds checking is not always
 
729
      performed. *)
 
730
 
 
731
  external unsafe_set: ('a, 'b, 'c) t -> int -> int -> int -> 'a -> unit
 
732
                     = "%caml_ba_unsafe_set_3"
 
733
  (** Like {!Bigarray.Array3.set}, but bounds checking is not always
 
734
      performed. *)
 
735
 
 
736
end
704
737
 
705
738
(** {6 Coercions between generic big arrays and fixed-dimension big arrays} *)
706
739
 
721
754
 
722
755
val array1_of_genarray : ('a, 'b, 'c) Genarray.t -> ('a, 'b, 'c) Array1.t
723
756
(** Return the one-dimensional big array corresponding to the given
724
 
   generic big array.  Raise [Invalid_arg] if the generic big array
 
757
   generic big array.  Raise [Invalid_argument] if the generic big array
725
758
   does not have exactly one dimension. *)
726
759
 
727
760
val array2_of_genarray : ('a, 'b, 'c) Genarray.t -> ('a, 'b, 'c) Array2.t
728
761
(** Return the two-dimensional big array corresponding to the given
729
 
   generic big array.  Raise [Invalid_arg] if the generic big array
 
762
   generic big array.  Raise [Invalid_argument] if the generic big array
730
763
   does not have exactly two dimensions. *)
731
764
 
732
765
val array3_of_genarray : ('a, 'b, 'c) Genarray.t -> ('a, 'b, 'c) Array3.t
733
766
(** Return the three-dimensional big array corresponding to the given
734
 
   generic big array.  Raise [Invalid_arg] if the generic big array
 
767
   generic big array.  Raise [Invalid_argument] if the generic big array
735
768
   does not have exactly three dimensions. *)
736
769
 
737
770
 
751
784
   The returned big array must have exactly the same number of
752
785
   elements as the original big array [b].  That is, the product
753
786
   of the dimensions of [b] must be equal to [i1 * ... * iN].
754
 
   Otherwise, [Invalid_arg] is raised. *)
 
787
   Otherwise, [Invalid_argument] is raised. *)
755
788
 
756
789
val reshape_1 : ('a, 'b, 'c) Genarray.t -> int -> ('a, 'b, 'c) Array1.t
757
790
(** Specialized version of {!Bigarray.reshape} for reshaping to