File: bigarray.h

package info (click to toggle)
ocaml 5.3.0-3
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 43,124 kB
  • sloc: ml: 355,439; ansic: 51,636; sh: 25,098; asm: 5,413; makefile: 3,673; python: 919; javascript: 273; awk: 253; perl: 59; fortran: 21; cs: 9
file content (121 lines) | stat: -rw-r--r-- 4,911 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
/**************************************************************************/
/*                                                                        */
/*                                 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.          */
/*                                                                        */
/**************************************************************************/

#ifndef CAML_BIGARRAY_H
#define CAML_BIGARRAY_H

#include "config.h"
#include "mlvalues.h"

typedef signed char caml_ba_int8;
typedef unsigned char caml_ba_uint8;
typedef int16_t caml_ba_int16;
typedef uint16_t caml_ba_uint16;

#define CAML_BA_MAX_NUM_DIMS 16

enum caml_ba_kind {
  CAML_BA_FLOAT32,             /* Single-precision floats */
  CAML_BA_FLOAT64,             /* Double-precision floats */
  CAML_BA_SINT8,               /* Signed 8-bit integers */
  CAML_BA_UINT8,               /* Unsigned 8-bit integers */
  CAML_BA_SINT16,              /* Signed 16-bit integers */
  CAML_BA_UINT16,              /* Unsigned 16-bit integers */
  CAML_BA_INT32,               /* Signed 32-bit integers */
  CAML_BA_INT64,               /* Signed 64-bit integers */
  CAML_BA_CAML_INT,            /* OCaml-style integers (signed 31 or 63 bits) */
  CAML_BA_NATIVE_INT,        /* Platform-native long integers (32 or 64 bits) */
  CAML_BA_COMPLEX32,           /* Single-precision complex */
  CAML_BA_COMPLEX64,           /* Double-precision complex */
  CAML_BA_CHAR,                /* Characters */
  CAML_BA_FLOAT16,             /* Half-precision floats */
  CAML_BA_FIRST_UNIMPLEMENTED_KIND,
};
#define CAML_BA_KIND_MASK 0xFF /* Mask for kind in flags field */

#define Caml_ba_kind_val(v) Int_val(v)

#define Val_caml_ba_kind(k) Val_int(k)

enum caml_ba_layout {
  CAML_BA_C_LAYOUT = 0,           /* Row major, indices start at 0 */
  CAML_BA_FORTRAN_LAYOUT = 0x100, /* Column major, indices start at 1 */
};
#define CAML_BA_LAYOUT_SHIFT 8    /* Bit offset of layout flag */
#define CAML_BA_LAYOUT_MASK 0x100 /* Mask for layout in flags field */

#define Caml_ba_layout_val(v) (Int_val(v) << CAML_BA_LAYOUT_SHIFT)

#define Val_caml_ba_layout(l) Val_int(l >> CAML_BA_LAYOUT_SHIFT)

enum caml_ba_managed {
  CAML_BA_EXTERNAL = 0,        /* Data is not allocated by OCaml */
  CAML_BA_MANAGED = 0x200,     /* Data is allocated by OCaml */
  CAML_BA_MAPPED_FILE = 0x400, /* Data is a memory mapped file */
};
#define CAML_BA_MANAGED_MASK 0x600 /* Mask for "managed" bits in flags field */

enum caml_ba_subarray {
  CAML_BA_SUBARRAY = 0x800     /* Data is shared with another bigarray */
};

struct caml_ba_proxy {
  atomic_uintnat refcount;      /* Reference count */
  void * data;                  /* Pointer to base of actual data */
  uintnat size;                 /* Size of data in bytes (if mapped file) */
};

struct caml_ba_array {
  void * data;                /* Pointer to raw data */
  intnat num_dims;            /* Number of dimensions */
  intnat flags;  /* Kind of element array + memory layout + allocation status */
  struct caml_ba_proxy * proxy; /* The proxy for sub-arrays, or NULL */
  intnat dim[]  /*[num_dims]*/; /* Size in each dimension */
};

/* Size of struct caml_ba_array, in bytes, without [dim] array */
#define SIZEOF_BA_ARRAY sizeof(struct caml_ba_array)

#define Caml_ba_array_val(v) ((struct caml_ba_array *) Data_custom_val(v))

#define Caml_ba_data_val(v) (Caml_ba_array_val(v)->data)

#ifdef __cplusplus
extern "C" {
#endif

CAMLextern value
    caml_ba_alloc(int flags, int num_dims, void * data, intnat * dim);
CAMLextern value caml_ba_alloc_dims(int flags, int num_dims, void * data,
                                 ... /*dimensions, with type intnat */);
CAMLextern uintnat caml_ba_byte_size(struct caml_ba_array * b);
CAMLextern uintnat caml_ba_num_elts(struct caml_ba_array * b);

#ifdef __cplusplus
}
#endif

#ifdef CAML_INTERNALS

CAMLextern int caml_ba_element_size[];
CAMLextern void caml_ba_finalize(value v);
CAMLextern int caml_ba_compare(value v1, value v2);
CAMLextern intnat caml_ba_hash(value v);
CAMLextern void caml_ba_serialize(value, uintnat *, uintnat *);
CAMLextern uintnat caml_ba_deserialize(void * dst);

#endif  /* CAML_INTERNALS */

#endif /* CAML_BIGARRAY_H */