A | |||
access_permission [UnixLabels] |
Flags for the
UnixLabels.access call.
| ||
access_permission [Unix] |
Flags for the
Unix.access call.
| ||
alarm [Gc] |
An alarm is a piece of data that calls a user function at the end of
each major GC cycle.
| ||
anchor [Tk] |
| ||
B | |||
big_int [Big_int] |
The type of big integers.
| ||
borderMode [Tk] | |||
C | |||
c_layout [Bigarray] | |||
channel [Event] |
The type of communication channels carrying values of type
'a .
| ||
color [Graphics] |
A color is specified by its R, G, B components.
| ||
control [Gc] |
The GC parameters are given as a
control record.
| ||
D | |||
dir_handle [UnixLabels] |
The type of descriptors over opened directories.
| ||
dir_handle [Unix] |
The type of descriptors over opened directories.
| ||
E | |||
elt [Set.S] |
The type of the set elements.
| ||
elt [MoreLabels.Set.S] | |||
error [UnixLabels] |
The type of error codes.
| ||
error [Unix] |
The type of error codes.
| ||
error [Dynlink] | |||
event [Tk] | |||
event [Graphics] |
To specify events to wait for.
| ||
event [Event] |
The type of communication events returning a result of type
'a .
| ||
eventField [Tk] | |||
eventInfo [Tk] | |||
extern_flags [Marshal] |
The flags to the
Marshal.to_* functions below.
| ||
F | |||
file_descr [UnixLabels] |
The abstract type of file descriptors.
| ||
file_descr [Unix] |
The abstract type of file descriptors.
| ||
file_kind [UnixLabels] | |||
file_kind [Unix] | |||
file_perm [UnixLabels] |
The type of file access rights.
| ||
file_perm [Unix] |
The type of file access rights.
| ||
fillMode [Tk] | |||
float32_elt [Bigarray] | |||
float64_elt [Bigarray] | |||
flow_action [UnixLabels] | |||
flow_action [Unix] | |||
flush_queue [UnixLabels] | |||
flush_queue [Unix] | |||
formatter [Format] |
Abstract data type corresponding to a pretty-printer and
all its machinery.
| ||
fortran_layout [Bigarray] |
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,
the other compatible with the Fortran conventions.
| ||
fpclass [Pervasives] |
The five classes of floating-point numbers, as determined by
the
Pervasives.classify_float function.
| ||
G | |||
group_entry [UnixLabels] |
Structure of entries in the
groups database.
| ||
group_entry [Unix] |
Structure of entries in the
groups database.
| ||
H | |||
host_entry [UnixLabels] |
Structure of entries in the
hosts database.
| ||
host_entry [Unix] |
Structure of entries in the
hosts database.
| ||
I | |||
image [Graphics] |
The abstract type for images, in internal representation.
| ||
in_channel [Pervasives] |
The type of input channel.
| ||
inet_addr [UnixLabels] |
The abstract type of Internet addresses.
| ||
inet_addr [Unix] |
The abstract type of Internet addresses.
| ||
int16_signed_elt [Bigarray] | |||
int16_unsigned_elt [Bigarray] | |||
int32_elt [Bigarray] | |||
int64_elt [Bigarray] | |||
int8_signed_elt [Bigarray] | |||
int8_unsigned_elt [Bigarray] | |||
int_elt [Bigarray] | |||
interval_timer [UnixLabels] |
The three kinds of interval timers.
| ||
interval_timer [Unix] |
The three kinds of interval timers.
| ||
interval_timer_status [UnixLabels] |
The type describing the status of an interval timer
| ||
interval_timer_status [Unix] |
The type describing the status of an interval timer
| ||
K | |||
key [MoreLabels.Map.S] | |||
key [MoreLabels.Hashtbl.S] | |||
key [Map.S] |
The type of the map keys.
| ||
key [Hashtbl.S] | |||
kind [Bigarray] |
To each element kind is associated a Caml type, which is
the type of Caml values that can be stored in the big array
or read back from it.
| ||
L | |||
layout [Bigarray] |
The type
'a layout represents one of the two supported
memory layouts: C-style if 'a is Bigarray.c_layout , Fortran-style
if 'a is Bigarray.fortran_layout .
| ||
lexbuf [Lexing] |
The type of lexer buffers.
| ||
linking_error [Dynlink] | |||
lock_command [UnixLabels] |
Commands for
UnixLabels.lockf .
| ||
lock_command [Unix] |
Commands for
Unix.lockf .
| ||
M | |||
modifier [Tk] | |||
msg_flag [UnixLabels] | |||
msg_flag [Unix] | |||
N | |||
nativeint_elt [Bigarray] | |||
num [Num] |
The type of numbers.
| ||
O | |||
open_flag [UnixLabels] |
The flags to
UnixLabels.openfile .
| ||
open_flag [Unix] |
The flags to
Unix.openfile .
| ||
open_flag [Pervasives] |
Opening modes for
Pervasives.open_out_gen and Pervasives.open_in_gen .
| ||
open_flag [Dbm] | |||
out_channel [Pervasives] |
The type of output channel.
| ||
P | |||
passwd_entry [UnixLabels] |
Structure of entries in the
passwd database.
| ||
passwd_entry [Unix] |
Structure of entries in the
passwd database.
| ||
process_status [UnixLabels] |
The termination status of a process.
| ||
process_status [Unix] |
The termination status of a process.
| ||
process_times [UnixLabels] |
The execution times (CPU times) of a process.
| ||
process_times [Unix] |
The execution times (CPU times) of a process.
| ||
protocol_entry [UnixLabels] |
Structure of entries in the
protocols database.
| ||
protocol_entry [Unix] |
Structure of entries in the
protocols database.
| ||
R | |||
ref [Pervasives] |
The type of references (mutable indirection cells) containing
a value of type
'a .
| ||
regexp [Str] |
The type of compiled regular expressions.
| ||
S | |||
seek_command [UnixLabels] |
Positioning modes for
UnixLabels.lseek .
| ||
seek_command [Unix] |
Positioning modes for
Unix.lseek .
| ||
service_entry [UnixLabels] |
Structure of entries in the
services database.
| ||
service_entry [Unix] |
Structure of entries in the
services database.
| ||
setattr_when [UnixLabels] | |||
setattr_when [Unix] | |||
shutdown_command [UnixLabels] |
The type of commands for
shutdown .
| ||
shutdown_command [Unix] |
The type of commands for
shutdown .
| ||
side [Tk] | |||
signal_behavior [Sys] | |||
sigprocmask_command [UnixLabels] | |||
sigprocmask_command [Unix] | |||
sockaddr [UnixLabels] | |||
sockaddr [Unix] | |||
socket_bool_option [UnixLabels] |
The socket options that can be consulted with
UnixLabels.getsockopt
and modified with UnixLabels.setsockopt .
| ||
socket_bool_option [Unix] |
The socket options that can be consulted with
Unix.getsockopt
and modified with Unix.setsockopt .
| ||
socket_domain [UnixLabels] |
The type of socket domains.
| ||
socket_domain [Unix] |
The type of socket domains.
| ||
socket_float_option [UnixLabels] |
The socket options that can be consulted with
UnixLabels.getsockopt_float
and modified with UnixLabels.setsockopt_float .
| ||
socket_float_option [Unix] |
The socket options that can be consulted with
Unix.getsockopt_float
and modified with Unix.setsockopt_float .
| ||
socket_int_option [UnixLabels] |
The socket options that can be consulted with
UnixLabels.getsockopt_int
and modified with UnixLabels.setsockopt_int .
| ||
socket_int_option [Unix] |
The socket options that can be consulted with
Unix.getsockopt_int
and modified with Unix.setsockopt_int .
| ||
socket_optint_option [UnixLabels] |
The socket options that can be consulted with
UnixLabels.getsockopt_optint
and modified with UnixLabels.setsockopt_optint .
| ||
socket_optint_option [Unix] |
The socket options that can be consulted with
Unix.getsockopt_optint
and modified with Unix.setsockopt_optint .
| ||
socket_type [UnixLabels] |
The type of socket kinds, specifying the semantics of
communications.
| ||
socket_type [Unix] |
The type of socket kinds, specifying the semantics of
communications.
| ||
spec [Arg] | |||
split_result [Str] | |||
stat [Gc] |
The memory management counters are returned in a
stat record.
| ||
state [Random] |
Values of this type are used to store the current state of the
generator.
| ||
stats [UnixLabels] |
The informations returned by the
UnixLabels.stat calls.
| ||
stats [Unix] |
The informations returned by the
Unix.stat calls.
| ||
status [Lazy] | |||
status [Graphics] |
To report events.
| ||
T | |||
t [Weak] |
The type of arrays of weak pointers (weak arrays).
| ||
t [Thread] |
The type of thread handles.
| ||
t [Stream] |
The type of streams holding values of type
'a .
| ||
t [Stack] |
The type of stacks containing elements of type
'a .
| ||
t [Set.S] |
The type of sets.
| ||
t [Queue] |
The type of queues containing elements of type
'a .
| ||
t [Obj] | |||
t [Mutex] |
The type of mutexes.
| ||
t [Set.OrderedType] |
The type of the set elements.
| ||
t [MoreLabels.Set.S] | |||
t [MoreLabels.Map.S] | |||
t [MoreLabels.Hashtbl.S] | |||
t [MoreLabels.Hashtbl] | |||
t [Map.OrderedType] |
The type of the map keys.
| ||
t [Map.S] |
The type of maps from type
key to type 'a .
| ||
t [Lazy] |
A value of type
'a Lazy.t is a deferred computation (also called a
suspension) that computes a result of type 'a .
| ||
t [Hashtbl.HashedType] |
The type of the hashtable keys.
| ||
t [Hashtbl.S] | |||
t [Hashtbl] |
The type of hash tables from type
'a to type 'b .
| ||
t [Digest] |
The type of digests: 16-character strings.
| ||
t [Dbm] |
The type of file descriptors opened on NDBM databases.
| ||
t [Condition] |
The type of condition variables.
| ||
t [Buffer] |
The abstract type of buffers.
| ||
t [Bigarray.Array3] |
The type of three-dimensional big arrays whose elements have
Caml type
'a , representation kind 'b , and memory layout 'c .
| ||
t [Bigarray.Array2] |
The type of two-dimensional big arrays whose elements have
Caml type
'a , representation kind 'b , and memory layout 'c .
| ||
t [Bigarray.Array1] |
The type of one-dimensional big arrays whose elements have
Caml type
'a , representation kind 'b , and memory layout 'c .
| ||
t [Bigarray.Genarray] |
The type
Genarray.t is the type of big arrays with variable
numbers of dimensions.
| ||
terminal_io [UnixLabels] | |||
terminal_io [Unix] | |||
tm [UnixLabels] |
The type representing wallclock time and calendar date.
| ||
tm [Unix] |
The type representing wallclock time and calendar date.
| ||
token [Genlex] |
The type of tokens.
| ||
U | |||
units [Tk] |
| ||
W | |||
wait_flag [UnixLabels] |
Flags for
UnixLabels.waitpid .
| ||
wait_flag [Unix] |
Flags for
Unix.waitpid .
| ||
window_id [GraphicsX11] |