aboutsummaryrefslogtreecommitdiffstats
path: root/tools/ocaml/libs/xb/xb.mli
blob: 20fe762d5d21c9164ce6ca55c0be403ca6c45590 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
module Op :
  sig
    type operation =
      Op.operation =
        Debug
      | Directory
      | Read
      | Getperms
      | Watch
      | Unwatch
      | Transaction_start
      | Transaction_end
      | Introduce
      | Release
      | Getdomainpath
      | Write
      | Mkdir
      | Rm
      | Setperms
      | Watchevent
      | Error
      | Isintroduced
      | Resume
      | Set_target
      | Restrict
    val operation_c_mapping : operation array
    val size : int
    val offset_pq : int
    val operation_c_mapping_pq : 'a array
    val size_pq : int
    val array_search : 'a -> 'a array -> int
    val of_cval : int -> operation
    val to_cval : operation -> int
    val to_string : operation -> string
  end
module Packet :
  sig
    type t =
      Packet.t = {
      tid : int;
      rid : int;
      ty : Op.operation;
      data : string;
    }
    exception Error of string
    exception DataError of string
    external string_of_header : int -> int -> int -> int -> string
      = "stub_string_of_header"
    val create : int -> int -> Op.operation -> string -> t
    val of_partialpkt : Partial.pkt -> t
    val to_string : t -> string
    val unpack : t -> int * int * Op.operation * string
    val get_tid : t -> int
    val get_ty : t -> Op.operation
    val get_data : t -> string
    val get_rid : t -> int
  end
exception End_of_file
exception Eagain
exception Noent
exception Invalid
type backend_mmap = {
  mmap : Xenmmap.mmap_interface;
  eventchn_notify : unit -> unit;
  mutable work_again : bool;
}
type backend_fd = { fd : Unix.file_descr; }
type backend = Fd of backend_fd | Xenmmap of backend_mmap
type partial_buf = HaveHdr of Partial.pkt | NoHdr of int * string
type t = {
  backend : backend;
  pkt_in : Packet.t Queue.t;
  pkt_out : Packet.t Queue.t;
  mutable partial_in : partial_buf;
  mutable partial_out : string;
}
val init_partial_in : unit -> partial_buf
val queue : t -> Packet.t -> unit
val read_fd : backend_fd -> 'a -> string -> int -> int
val read_mmap : backend_mmap -> 'a -> string -> int -> int
val read : t -> string -> int -> int
val write_fd : backend_fd -> 'a -> string -> int -> int
val write_mmap : backend_mmap -> 'a -> string -> int -> int
val write : t -> string -> int -> int
val output : t -> bool
val input : t -> bool
val newcon : backend -> t
val open_fd : Unix.file_descr -> t
val open_mmap : Xenmmap.mmap_interface -> (unit -> unit) -> t
val close : t -> unit
val is_fd : t -> bool
val is_mmap : t -> bool
val output_len : t -> int
val has_new_output : t -> bool
val has_old_output : t -> bool
val has_output : t -> bool
val peek_output : t -> Packet.t
val input_len : t -> int
val has_in_packet : t -> bool
val get_in_packet : t -> Packet.t
val has_more_input : t -> bool
val is_selectable : t -> bool
val get_fd : t -> Unix.file_descr