aboutsummaryrefslogtreecommitdiffstats
path: root/tools/ocaml/libs/xb/xb.mli
blob: 6cbf0a84fe0da912e3829f317632a9dd76753b4b (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
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 to_string : operation -> string
end

module Packet:
sig
	type t

	exception Error of string
	exception DataError of string

	val create : int -> int -> Op.operation -> string -> t
	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 t

(** queue a packet into the output queue for later sending *)
val queue : t -> Packet.t -> unit

(** process the output queue, return if a packet has been totally sent *)
val output : t -> bool

(** process the input queue, return if a packet has been totally received *)
val input : t -> bool

(** create new connection using a fd interface *)
val open_fd : Unix.file_descr -> t
(** create new connection using a mmap intf and a function to notify eventchn *)
val open_mmap : Mmap.mmap_interface -> (unit -> unit) -> t

(* close a connection *)
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