Update Red Hat Copyright Notices
[nbdkit.git] / plugins / ocaml / NBDKit.mli
blob81447d07d2072c7a692d7dfadc5bf8d83d994f93
1 (* hey emacs, this is OCaml code: -*- tuareg -*- *)
2 (* nbdkit OCaml interface
3 * Copyright Red Hat
5 * Redistribution and use in source and binary forms, with or without
6 * modification, are permitted provided that the following conditions are
7 * met:
9 * * Redistributions of source code must retain the above copyright
10 * notice, this list of conditions and the following disclaimer.
12 * * Redistributions in binary form must reproduce the above copyright
13 * notice, this list of conditions and the following disclaimer in the
14 * documentation and/or other materials provided with the distribution.
16 * * Neither the name of Red Hat nor the names of its contributors may be
17 * used to endorse or promote products derived from this software without
18 * specific prior written permission.
20 * THIS SOFTWARE IS PROVIDED BY RED HAT AND CONTRIBUTORS ''AS IS'' AND
21 * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO,
22 * THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A
23 * PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL RED HAT OR
24 * CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
25 * SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
26 * LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF
27 * USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND
28 * ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY,
29 * OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT
30 * OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
31 * SUCH DAMAGE.
34 (** Interface between plugins written in OCaml and the nbdkit server.
36 Read these man pages for additional information:
37 nbdkit-ocaml-plugin(3) and nbdkit-plugin(3) *)
39 (** Flags passed from the server to various callbacks. *)
40 type flags = flag list
41 and flag = May_trim | FUA | Req_one
43 type fua_flag = FuaNone | FuaEmulate | FuaNative
45 type cache_flag = CacheNone | CacheEmulate | CacheNop
47 (** The type of the extent list returned by [extents] *)
48 type extent = {
49 offset : int64;
50 length : int64;
51 is_hole : bool;
52 is_zero : bool;
55 (** The type of the export list returned by [list_exports] *)
56 type export = {
57 name : string;
58 description : string option;
61 (** The type of the thread model returned by [thread_model] *)
62 type thread_model =
63 | THREAD_MODEL_SERIALIZE_CONNECTIONS
64 | THREAD_MODEL_SERIALIZE_ALL_REQUESTS
65 | THREAD_MODEL_SERIALIZE_REQUESTS
66 | THREAD_MODEL_PARALLEL
68 (** Register the plugin with nbdkit.
70 The ['a] parameter is the handle type returned by your
71 [open_connection] method and passed back to all connected calls. *)
72 val register_plugin :
73 (* Plugin description. *)
74 name: string ->
75 ?longname: string ->
76 ?version: string ->
77 ?description: string ->
79 (* Plugin lifecycle. *)
80 ?load: (unit -> unit) ->
81 ?get_ready: (unit -> unit) ->
82 ?after_fork: (unit -> unit) ->
83 ?cleanup: (unit -> unit) ->
84 ?unload: (unit -> unit) ->
86 (* Plugin configuration. *)
87 ?config: (string -> string -> unit) ->
88 ?config_complete: (unit -> unit) ->
89 ?config_help: string ->
90 ?thread_model: (unit -> thread_model) ->
91 ?magic_config_key: string ->
93 (* Connection lifecycle. *)
94 ?preconnect: (bool -> unit) ->
95 open_connection: (bool -> 'a) ->
96 ?close: ('a -> unit) ->
98 (* NBD negotiation. *)
99 get_size: ('a -> int64) ->
100 ?block_size: ('a -> int * int * int64) ->
101 ?can_cache: ('a -> cache_flag) ->
102 ?can_extents: ('a -> bool) ->
103 ?can_fast_zero: ('a -> bool) ->
104 ?can_flush: ('a -> bool) ->
105 ?can_fua: ('a -> fua_flag) ->
106 ?can_multi_conn: ('a -> bool) ->
107 ?can_trim: ('a -> bool) ->
108 ?can_write: ('a -> bool) ->
109 ?can_zero: ('a -> bool) ->
110 ?is_rotational: ('a -> bool) ->
112 (* Serving data. *)
113 pread: ('a -> int -> int64 -> flags -> string) ->
114 ?pwrite: ('a -> string -> int64 -> flags -> unit) ->
115 ?flush: ('a -> flags -> unit) ->
116 ?trim: ('a -> int64 -> int64 -> flags -> unit) ->
117 ?zero: ('a -> int64 -> int64 -> flags -> unit) ->
118 ?extents: ('a -> int64 -> int64 -> flags -> extent list) ->
119 ?cache: ('a -> int64 -> int64 -> flags -> unit) ->
121 (* Miscellaneous. *)
122 ?dump_plugin: (unit -> unit) ->
123 ?list_exports: (bool -> bool -> export list) ->
124 ?default_export: (bool -> bool -> string) ->
125 ?export_description: ('a -> string) ->
127 unit ->
128 unit
130 (** Set the errno returned over the NBD protocol to the client.
132 Notice however that the NBD protocol only supports a small
133 handful of errno values. Any other errno will be translated
134 into [EINVAL]. *)
135 val set_error : Unix.error -> unit
137 (** Bindings for [nbdkit_parse_size], [nbdkit_parse_bool] and
138 [nbdkit_read_password]. See nbdkit-plugin(3) for information
139 about these functions.
141 On error these functions all raise [Invalid_argument]. The
142 actual error is sent to the nbdkit error log and is not
143 available from the OCaml code. It is usually best to let
144 the exception escape. *)
145 (* Note OCaml has functions already for parsing other integers, so
146 * there is no need to bind them here. We only bind the functions
147 * which have special abilities in nbdkit: [parse_size] can parse
148 * human sizes, [parse_bool] parses a range of nbdkit-specific
149 * boolean strings, and [read_password] suppresses echo.
151 val parse_size : string -> int64
152 val parse_bool : string -> bool
153 val read_password : string -> string
155 (** Binding for [nbdkit_realpath].
156 Returns the canonical path from a path parameter. *)
157 (* OCaml's [Filename] module can handle [absolute_path]. *)
158 val realpath : string -> string
160 (** Binding for [nbdkit_nanosleep]. Sleeps for seconds and nanoseconds. *)
161 val nanosleep : int -> int -> unit
163 (** Binding for [nbdkit_export_name]. Returns the name of the
164 export as requested by the client. *)
165 val export_name : unit -> string
167 (** Binding for [nbdkit_shutdown]. Requests the server shut down. *)
168 val shutdown : unit -> unit
170 (** Binding for [nbdkit_disconnect]. Requests disconnecting current client. *)
171 val disconnect : bool -> unit
173 (** Print a debug message when nbdkit is in verbose mode. *)
174 val debug : ('a, unit, string, unit) format4 -> 'a
176 (** Return the version of nbdkit that the plugin was compiled with. *)
177 val version : unit -> string
179 (** Return the nbdkit API version used by the plugin.
181 See [NBDKIT_API_VERSION] in nbdkit-plugin(3). *)
182 val api_version : unit -> int
184 (** Binding for [nbdkit_peer_pid]. *)
185 val peer_pid : unit -> int64
187 (** Binding for [nbdkit_peer_uid]. *)
188 val peer_uid : unit -> int64
190 (** Binding for [nbdkit_peer_gid]. *)
191 val peer_gid : unit -> int64