module Ctypes:sig..end
The main points of interest are the set of functions for describing C
types (see types) and the set of functions for accessing C values (see
Values representing C values). The Foreign.foreign function uses C type descriptions
to bind external C values.
type('a, 'b)pointer =('a, 'b) Ctypes_static.pointer
('a, [`C]) pointer contains
a C-compatible pointer, and a value of type ('a, [`OCaml]) pointer
contains a pointer to a value that can be moved by OCaml runtime.type'aptr =('a, [ `C ]) pointer
t ptr can be
used to read and write values of type t at particular addresses.type'aocaml ='a Ctypes_static.ocaml
'a ocaml pointers must not invoke
any OCaml code.type'acarray ='a Ctypes_static.carray
t carray can be used to read
and write array objects in C-managed storage.type'abigarray_class ='a Ctypes_static.bigarray_class
val genarray : < ba_repr : 'b; bigarray : ('a, 'b, 'l) Bigarray.Genarray.t;
carray : 'a carray; dims : int array; element : 'a; layout : 'l >
bigarray_classBigarray.Genarray.t valuesval array1 : < ba_repr : 'b; bigarray : ('a, 'b, 'l) Bigarray.Array1.t;
carray : 'a carray; dims : int; element : 'a; layout : 'l >
bigarray_classBigarray.Array1.t valuesval array2 : < ba_repr : 'b; bigarray : ('a, 'b, 'l) Bigarray.Array2.t;
carray : 'a carray carray; dims : int * int; element : 'a;
layout : 'l >
bigarray_classBigarray.Array2.t valuesval array3 : < ba_repr : 'b; bigarray : ('a, 'b, 'l) Bigarray.Array3.t;
carray : 'a carray carray carray;
dims : int * int * int; element : 'a; layout : 'l >
bigarray_classBigarray.Array3.t valuestype('a, 'kind)structured =('a, 'kind) Ctypes_static.structured
'kind parameter is a polymorphic variant type indicating whether the type
represents a struct (`Struct) or a union (`Union).type'astructure =('a, [ `Struct ]) structured
type'aunion =('a, [ `Union ]) structured
type('a, 't)field =('a, 't) Ctypes_static.field
(a, s) field represents a field of type a in a
struct or union of type s.type'aabstract ='a Ctypes_static.abstract
abstract type is to
represent values whose type varies from platform to platform.
For example, the type pthread_t is a pointer on some platforms, an
integer on other platforms, and a struct on a third set of platforms. One
way to deal with this kind of situation is to have
possibly-platform-specific code which interrogates the C type in some way
to help determine an appropriate representation. Another way is to use
abstract, leaving the representation opaque.
(Note, however, that although pthread_t is a convenient example, since
the type used to implement it varies significantly across platforms, it's
not actually a good match for abstract, since values of type pthread_t
are passed and returned by value.)
include Ctypes_types.TYPE
val sizeof : 'a typ -> intsizeof t computes the size in bytes of the type t. The exception
Ctypes.IncompleteType is raised if t is incomplete.val alignment : 'a typ -> intalignment t computes the alignment requirements of the type t. The
exception Ctypes.IncompleteType is raised if t is incomplete.val format_typ : ?name:string -> Format.formatter -> 'a typ -> unitval format_fn : ?name:string -> Format.formatter -> 'a fn -> unitval string_of_typ : ?name:string -> 'a typ -> stringval string_of_fn : ?name:string -> 'a fn -> stringval format : 'a typ -> Format.formatter -> 'a -> unitval string_of : 'a typ -> 'a -> stringval null : unit ptrval (!@) : 'a ptr -> 'a!@ p dereferences the pointer p. If the reference type is a scalar
type then dereferencing constructs a new value. If the reference type is
an aggregate type then dereferencing returns a value that references the
memory pointed to by p.val (<-@) : 'a ptr -> 'a -> unitp <-@ v writes the value v to the address p.val (+@) : ('a, 'b) pointer -> int -> ('a, 'b) pointerp is a pointer to an array element then p +@ n computes the
address of the nth next element.val (-@) : ('a, 'b) pointer -> int -> ('a, 'b) pointerp is a pointer to an array element then p -@ n computes the address
of the nth previous element.val ptr_diff : ('a, 'b) pointer -> ('a, 'b) pointer -> intptr_diff p q computes q - p. As in C, both p and q must point
into the same array, and the result value is the difference of the
subscripts of the two array elements.val from_voidp : 'a typ -> unit ptr -> 'a ptrvoid *.val to_voidp : 'a ptr -> unit ptrvoid *.val allocate : ?finalise:('a ptr -> unit) -> 'a typ -> 'a -> 'a ptrallocate t v allocates a fresh value of type t, initialises it
with v and returns its address. The argument ?finalise, if
present, will be called just before the memory is freed. The value
will be automatically freed after no references to the pointer
remain within the calling OCaml program.val allocate_n : ?finalise:('a ptr -> unit) -> 'a typ -> count:int -> 'a ptrallocate_n t ~count:n allocates a fresh array with element type
t and length n, and returns its address. The argument
?finalise, if present, will be called just before the memory is
freed. The array will be automatically freed after no references
to the pointer remain within the calling OCaml program. The
memory is allocated with libc's calloc and is guaranteed to be
zero-filled.val ptr_compare : 'a ptr -> 'a ptr -> intp and q are pointers to elements i and j of the same array then
ptr_compare p q compares the indexes of the elements. The result is
negative if i is less than j, positive if i is greater than j, and
zero if i and j are equal.val is_null : 'a ptr -> boolis_null p is true when p is a null pointer.val reference_type : 'a ptr -> 'a typval ptr_of_raw_address : nativeint -> unit ptrval funptr_of_raw_address : nativeint -> (unit -> unit) Ctypes_static.static_funptrval raw_address_of_ptr : unit ptr -> nativeintraw_address_of_ptr p returns the numeric representation of p.
Note that the return value remains valid only as long as the pointed-to
object is alive. If p is a managed object (e.g. a value returned by
Ctypes.make) then unless the caller retains a reference to p, the object may
be collected, invalidating the returned address.
val string_from_ptr : char ptr -> length:int -> stringstring_from_ptr p ~length creates a string initialized with the length
characters at address p.
Raise Invalid_argument "Ctypes.string_from_ptr" if length is
negative.
val ocaml_string_start : string -> string ocamlocaml_string_start s allows to pass a pointer to the contents of an OCaml
string directly to a C function.val ocaml_bytes_start : Bytes.t -> Bytes.t ocamlocaml_bytes_start s allows to pass a pointer to the contents of an OCaml
byte array directly to a C function.module CArray:sig..end
val bigarray_start : < ba_repr : 'c; bigarray : 'b; carray : 'd; dims : 'e; element : 'a;
layout : 'l >
bigarray_class -> 'b -> 'a ptrval bigarray_of_ptr : < ba_repr : 'f; bigarray : 'b; carray : 'c; dims : 'i; element : 'a;
layout : Bigarray.c_layout >
bigarray_class -> 'i -> ('a, 'f) Bigarray.kind -> 'a ptr -> 'bbigarray_of_ptr c dims k p converts the C pointer p to a C-layout
bigarray value. No copy is made; the bigarray references the memory
pointed to by p.val fortran_bigarray_of_ptr : < ba_repr : 'f; bigarray : 'b; carray : 'c; dims : 'i; element : 'a;
layout : Bigarray.fortran_layout >
bigarray_class -> 'i -> ('a, 'f) Bigarray.kind -> 'a ptr -> 'bfortran_bigarray_of_ptr c dims k p converts the C pointer p to a
Fortran-layout bigarray value. No copy is made; the bigarray references
the memory pointed to by p.val array_of_bigarray : < ba_repr : 'a; bigarray : 'b; carray : 'c; dims : 'd; element : 'e;
layout : Bigarray.c_layout >
bigarray_class -> 'b -> 'carray_of_bigarray c b converts the bigarray value b to a value of type
Ctypes.CArray.t. No copy is made; the result occupies the same memory as
b.val bigarray_of_array : < ba_repr : 'f; bigarray : 'b; carray : 'c carray; dims : 'i;
element : 'a; layout : Bigarray.c_layout >
bigarray_class -> ('a, 'f) Bigarray.kind -> 'c carray -> 'bbigarray_of_array c k a converts the Ctypes.CArray.t value a to a
C-layout bigarray value. No copy is made; the result occupies the
same memory as a.val make : ?finalise:(('a, 'b) structured -> unit) ->
('a, 'b) structured typ -> ('a, 'b) structured?finalise, if present, will be called just before the underlying memory is
freed.val setf : ('b, 'c) structured ->
('a, ('b, 'c) structured) field -> 'a -> unitsetf s f v overwrites the value of the field f in the structure or
union s with v.val getf : ('b, 'c) structured ->
('a, ('b, 'c) structured) field -> 'agetf s f retrieves the value of the field f in the structure or union
s. The semantics for non-scalar types are non-copying, as for
Ctypes.(!@).val (@.) : ('b, 'c) structured ->
('a, ('b, 'c) structured) field -> 'a ptrs @. f computes the address of the field f in the structure or union
value s.val (|->) : ('b, 'c) structured ptr ->
('a, ('b, 'c) structured) field -> 'a ptrp |-> f computes the address of the field f in the structure or union
value pointed to by p.val offsetof : ('a, 'b structure) field -> intoffsetof f returns the offset, in bytes, of the field f from the
beginning of the associated struct type.val field_type : ('a, 'b) field -> 'a typfield_type f returns the type of the field f.val field_name : ('a, 'b) field -> stringfield_name f returns the name of the field f.val addr : ('a, 'b) structured -> ('a, 'b) structured ptraddr s returns the address of the structure or union s.val coerce : 'a typ -> 'b typ -> 'a -> 'bcoerce t1 t2 returns a coercion function between the types represented
by t1 and t2. If t1 cannot be coerced to t2, coerce raises
Ctypes.Uncoercible.
The following coercions are currently supported:
voidview and another type t (in either
direction) if there is a coercion between the representation type
underlying the view and t.t1 is coercible to t2 and t2 is
coercible to t3, then t1 is directly coercible to t3.val coerce_fn : 'a fn -> 'b fn -> 'a -> 'bcoerce_fn f1 f2 returns a coercion function between the function
types represented by f1 and f2. If f1 cannot be coerced to
f2, coerce_fn raises Ctypes.Uncoercible.
A function type f1 may be coerced to another function type f2
if all of the following hold:
f1 and f2 have the same arityf2 may be coerced to the corresponding
argument of f1f1 may be coerced to the return type of f2module type FOREIGN =sig..end
module Root:sig..end
exception Unsupported of string
exception ModifyingSealedType of string
exception IncompleteType
The incomplete types are struct and union types that have not been sealed, and the void type.
It is not permitted to compute the size or alignment requirements of an
incomplete type, to use it as a struct or union member, to read or write a
value of the type through a pointer or to use it as the referenced type in
pointer arithmetic. Additionally, incomplete struct and union types
cannot be used as argument or return types.
type uncoercible_info
exception Uncoercible of uncoercible_info