summaryrefslogtreecommitdiffstats
path: root/otherlibs/dynlink
diff options
context:
space:
mode:
authorMaxence Guesdon <maxence.guesdon@inria.fr>2001-12-04 16:59:56 +0000
committerMaxence Guesdon <maxence.guesdon@inria.fr>2001-12-04 16:59:56 +0000
commit639d7afb5c0c5e2038f7dd966091014d4bb12a16 (patch)
treebacc4ac78ead7323740c733594ae0f34f3e94f39 /otherlibs/dynlink
parent7c41a9c9e6c97cb0c9dd20f16bc9594e5ad35aea (diff)
commentaires après
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@4101 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'otherlibs/dynlink')
-rw-r--r--otherlibs/dynlink/dynlink.mli19
1 files changed, 10 insertions, 9 deletions
diff --git a/otherlibs/dynlink/dynlink.mli b/otherlibs/dynlink/dynlink.mli
index 061a2c821..b3916e6ff 100644
--- a/otherlibs/dynlink/dynlink.mli
+++ b/otherlibs/dynlink/dynlink.mli
@@ -14,21 +14,22 @@
(** Dynamic loading of bytecode object files. *)
-(** Initialize the library. Must be called before [loadfile]. *)
val init : unit -> unit
+(** Initialize the library. Must be called before [loadfile]. *)
+val loadfile : string -> unit
(** Load the given bytecode object file and link it.
All toplevel expressions in the loaded compilation unit
are evaluated. No facilities are provided to
access value names defined by the unit. Therefore, the unit
must register itself its entry points with the main program,
e.g. by modifying tables of functions. *)
-val loadfile : string -> unit
+val loadfile_private : string -> unit
(** Same as [loadfile], except that the module loaded is not
made available to other modules dynamically loaded afterwards. *)
-val loadfile_private : string -> unit
+val add_interfaces : string list -> string list -> unit
(** [add_interfaces units path] grants dynamically-linked object
files access to the compilation units named in list [units].
The interfaces ([.cmi] files) for these units are searched in
@@ -37,30 +38,30 @@ val loadfile_private : string -> unit
units composing the running program, not even the standard library.
[add_interfaces] or {!Dynlink.add_available_units} (see below) must be
called to grant access to some of the units. *)
-val add_interfaces : string list -> string list -> unit
+val add_available_units : (string * Digest.t) list -> unit
(** Same as {!Dynlink.add_interfaces}, but instead of searching [.cmi] files
to find the unit interfaces, uses the interface digests given
for each unit. This way, the [.cmi] interface files need not be
available at run-time. The digests can be extracted from [.cmi]
files using the [extract_crc] program installed in the
Objective Caml standard library directory. *)
-val add_available_units : (string * Digest.t) list -> unit
-(** Clear the list of compilation units accessible to dynamically-linked programs. *)
val clear_available_units : unit -> unit
+(** Clear the list of compilation units accessible to dynamically-linked programs. *)
+val allow_unsafe_modules : bool -> unit
(** Govern whether unsafe object files are allowed to be
dynamically linked. A compilation unit is ``unsafe'' if it contains
declarations of external functions, which can break type safety.
By default, dynamic linking of unsafe object files is
not allowed. *)
-val allow_unsafe_modules : bool -> unit
type linking_error =
Undefined_global of string
| Unavailable_primitive of string
| Uninitialized_global of string
+
type error =
Not_a_bytecode_file of string
| Inconsistent_import of string
@@ -71,12 +72,12 @@ type error =
| File_not_found of string
| Cannot_open_dll of string
+exception Error of error
(** Errors in dynamic linking are reported by raising the [Error]
exception with a description of the error. *)
-exception Error of error
+val error_message : error -> string
(** Convert an error description to a printable message. *)
-val error_message: error -> string
(**/**)