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
17let debug fmt = Logging.debug "domains" fmt
18let error fmt = Logging.error "domains" fmt
19let warn fmt  = Logging.warn  "domains" fmt
20
21let xc = Xenctrl.interface_open ()
22
23type domains = {
24	eventchn: Event.t;
25	table: (Xenctrl.domid, Domain.t) Hashtbl.t;
26
27	(* N.B. the Queue module is not thread-safe but oxenstored is single-threaded. *)
28	(* Domains queue up to regain conflict-credit; we have a queue for
29	   domains that are carrying some penalty and so are below the
30	   maximum credit, and another queue for domains that have run out of
31	   credit and so have had their access paused. *)
32	doms_conflict_paused: (Domain.t option ref) Queue.t;
33	doms_with_conflict_penalty: (Domain.t option ref) Queue.t;
34
35	(* A callback function to be called when we go from zero to one paused domain.
36	   This will be to reset the countdown until the next unit of credit is issued. *)
37	on_first_conflict_pause: unit -> unit;
38
39	(* If config is set to use individual instead of aggregate conflict-rate-limiting,
40	   we use these counts instead of the queues. The second one includes the first. *)
41	mutable n_paused: int;    (* Number of domains with zero or negative credit *)
42	mutable n_penalised: int; (* Number of domains with less than maximum credit *)
43}
44
45let init eventchn on_first_conflict_pause = {
46	eventchn = eventchn;
47	table = Hashtbl.create 10;
48	doms_conflict_paused = Queue.create ();
49	doms_with_conflict_penalty = Queue.create ();
50	on_first_conflict_pause = on_first_conflict_pause;
51	n_paused = 0;
52	n_penalised = 0;
53}
54let del doms id = Hashtbl.remove doms.table id
55let exist doms id = Hashtbl.mem doms.table id
56let find doms id = Hashtbl.find doms.table id
57let number doms = Hashtbl.length doms.table
58let iter doms fct = Hashtbl.iter (fun _ b -> fct b) doms.table
59
60let rec is_empty_queue q =
61	Queue.is_empty q ||
62		if !(Queue.peek q) = None
63		then (
64			ignore (Queue.pop q);
65			is_empty_queue q
66		) else false
67
68let all_at_max_credit doms =
69	if !Define.conflict_rate_limit_is_aggregate
70	then
71		(* Check both becuase if burst limit is 1.0 then a domain can go straight
72		 * from max-credit to paused without getting into the penalty queue. *)
73		is_empty_queue doms.doms_with_conflict_penalty
74		&& is_empty_queue doms.doms_conflict_paused
75	else doms.n_penalised = 0
76
77(* Functions to handle queues of domains given that the domain might be deleted while in a queue. *)
78let push dom queue =
79	Queue.push (ref (Some dom)) queue
80
81let rec pop queue =
82	match !(Queue.pop queue) with
83	| None -> pop queue
84	| Some x -> x
85
86let remove_from_queue dom queue =
87	Queue.iter (fun d -> match !d with
88		| None -> ()
89		| Some x -> if x=dom then d := None) queue
90
91let cleanup doms =
92	let notify = ref false in
93	let dead_dom = ref [] in
94
95	Hashtbl.iter (fun id _ -> if id <> 0 then
96		try
97			let info = Xenctrl.domain_getinfo xc id in
98			if info.Xenctrl.shutdown || info.Xenctrl.dying then (
99				debug "Domain %u died (dying=%b, shutdown %b -- code %d)"
100				                    id info.Xenctrl.dying info.Xenctrl.shutdown info.Xenctrl.shutdown_code;
101				if info.Xenctrl.dying then
102					dead_dom := id :: !dead_dom
103				else
104					notify := true;
105			)
106		with Xenctrl.Error _ ->
107			debug "Domain %u died -- no domain info" id;
108			dead_dom := id :: !dead_dom;
109		) doms.table;
110	List.iter (fun id ->
111		let dom = Hashtbl.find doms.table id in
112		Domain.close dom;
113		Hashtbl.remove doms.table id;
114		if dom.Domain.conflict_credit <= !Define.conflict_burst_limit
115		then (
116			remove_from_queue dom doms.doms_with_conflict_penalty;
117			if (dom.Domain.conflict_credit <= 0.) then remove_from_queue dom doms.doms_conflict_paused
118		)
119	) !dead_dom;
120	!notify, !dead_dom
121
122let resume _doms _domid =
123	()
124
125let create doms domid mfn port =
126	let interface = Xenctrl.map_foreign_range xc domid (Xenmmap.getpagesize()) mfn in
127	let dom = Domain.make domid mfn port interface doms.eventchn in
128	Hashtbl.add doms.table domid dom;
129	Domain.bind_interdomain dom;
130	dom
131
132let xenstored_kva = ref ""
133let xenstored_port = ref ""
134
135let create0 doms =
136	let port, interface =
137		(
138			let port = Utils.read_file_single_integer !xenstored_port
139			and fd = Unix.openfile !xenstored_kva
140					       [ Unix.O_RDWR ] 0o600 in
141			let interface = Xenmmap.mmap fd Xenmmap.RDWR Xenmmap.SHARED
142						  (Xenmmap.getpagesize()) 0 in
143			Unix.close fd;
144			port, interface
145		)
146		in
147	let dom = Domain.make 0 Nativeint.zero port interface doms.eventchn in
148	Hashtbl.add doms.table 0 dom;
149	Domain.bind_interdomain dom;
150	Domain.notify dom;
151	dom
152
153let decr_conflict_credit doms dom =
154	dom.Domain.caused_conflicts <- Int64.add 1L dom.Domain.caused_conflicts;
155	let before = dom.Domain.conflict_credit in
156	let after = max (-1.0) (before -. 1.0) in
157	debug "decr_conflict_credit dom%d %F -> %F" (Domain.get_id dom) before after;
158	dom.Domain.conflict_credit <- after;
159	let newly_penalised =
160		before >= !Define.conflict_burst_limit
161		&& after < !Define.conflict_burst_limit in
162	let newly_paused = before > 0.0 && after <= 0.0 in
163	if !Define.conflict_rate_limit_is_aggregate then (
164		if newly_penalised
165		&& after > 0.0
166		then (
167			push dom doms.doms_with_conflict_penalty
168		) else if newly_paused
169		then (
170			let first_pause = Queue.is_empty doms.doms_conflict_paused in
171			push dom doms.doms_conflict_paused;
172			if first_pause then doms.on_first_conflict_pause ()
173		) else (
174			(* The queues are correct already: no further action needed. *)
175		)
176	) else (
177		if newly_penalised then doms.n_penalised <- doms.n_penalised + 1;
178		if newly_paused then (
179			doms.n_paused <- doms.n_paused + 1;
180			if doms.n_paused = 1 then doms.on_first_conflict_pause ()
181		)
182	)
183
184(* Give one point of credit to one domain, and update the queues appropriately. *)
185let incr_conflict_credit_from_queue doms =
186	let process_queue q requeue_test =
187		let d = pop q in
188		let before = d.Domain.conflict_credit in (* just for debug-logging *)
189		d.Domain.conflict_credit <- min (d.Domain.conflict_credit +. 1.0) !Define.conflict_burst_limit;
190		debug "incr_conflict_credit_from_queue: dom%d: %F -> %F" (Domain.get_id d) before d.Domain.conflict_credit;
191		if requeue_test d.Domain.conflict_credit then (
192			push d q (* Make it queue up again for its next point of credit. *)
193		)
194	in
195	let paused_queue_test cred = cred <= 0.0 in
196	let penalty_queue_test cred = cred < !Define.conflict_burst_limit in
197	try process_queue doms.doms_conflict_paused paused_queue_test
198	with Queue.Empty -> (
199		try process_queue doms.doms_with_conflict_penalty penalty_queue_test
200		with Queue.Empty -> () (* Both queues are empty: nothing to do here. *)
201	)
202
203let incr_conflict_credit doms =
204	if !Define.conflict_rate_limit_is_aggregate
205	then incr_conflict_credit_from_queue doms
206	else (
207		(* Give a point of credit to every domain, subject only to the cap. *)
208		let inc dom =
209			let before = dom.Domain.conflict_credit in
210			let after = min (before +. 1.0) !Define.conflict_burst_limit in
211			dom.Domain.conflict_credit <- after;
212			debug "incr_conflict_credit dom%d: %F -> %F" (Domain.get_id dom) before after;
213
214			if before <= 0.0 && after > 0.0
215			then doms.n_paused <- doms.n_paused - 1;
216
217			if before < !Define.conflict_burst_limit
218			&& after >= !Define.conflict_burst_limit
219			then doms.n_penalised <- doms.n_penalised - 1
220		in
221		if doms.n_penalised > 0 then iter doms inc
222	)
223