1(*
2 * Copyright (C) 2006-2007 XenSource Ltd.
3 * Copyright (C) 2008      Citrix Ltd.
4 * Author Vincent Hanquez <vincent.hanquez@eu.citrix.com>
5 *
6 * This program is free software; you can redistribute it and/or modify
7 * it under the terms of the GNU Lesser General Public License as published
8 * by the Free Software Foundation; version 2.1 only. with the special
9 * exception on linking described in file LICENSE.
10 *
11 * This program is distributed in the hope that it will be useful,
12 * but WITHOUT ANY WARRANTY; without even the implied warranty of
13 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14 * GNU Lesser General Public License for more details.
15 *)
16
17module Server_feature = struct
18  type t =
19    | Reconnection
20end
21
22module Server_features = Set.Make(struct
23    type t = Server_feature.t
24    let compare = compare
25  end)
26
27external read: Xenmmap.mmap_interface -> bytes -> int -> int = "ml_interface_read"
28external write_substring: Xenmmap.mmap_interface -> string -> int -> int = "ml_interface_write"
29
30external _internal_set_server_features: Xenmmap.mmap_interface -> int -> unit = "ml_interface_set_server_features" [@@noalloc]
31external _internal_get_server_features: Xenmmap.mmap_interface -> int = "ml_interface_get_server_features" [@@noalloc]
32
33let get_server_features mmap =
34  (* NB only one feature currently defined above *)
35  let x = _internal_get_server_features mmap in
36  if x = 0
37  then Server_features.empty
38  else Server_features.singleton Server_feature.Reconnection
39
40let set_server_features mmap set =
41  (* NB only one feature currently defined above *)
42  let x = if set = Server_features.empty then 0 else 1 in
43  _internal_set_server_features mmap x
44
45external close: Xenmmap.mmap_interface -> unit = "ml_interface_close" [@@noalloc]
46