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
17 #define _XOPEN_SOURCE 600
18 #include <stdlib.h>
19 #include <errno.h>
20
21 #define CAML_NAME_SPACE
22 #include <caml/alloc.h>
23 #include <caml/memory.h>
24 #include <caml/signals.h>
25 #include <caml/fail.h>
26 #include <caml/callback.h>
27
28 #include <sys/mman.h>
29 #include <stdint.h>
30 #include <string.h>
31
32 #define XC_WANT_COMPAT_MAP_FOREIGN_API
33 #include <xenctrl.h>
34
35 #include "mmap_stubs.h"
36
37 #define PAGE_SHIFT 12
38 #define PAGE_SIZE (1UL << PAGE_SHIFT)
39 #define PAGE_MASK (~(PAGE_SIZE-1))
40
41 #define _H(__h) ((xc_interface *)(__h))
42 #define _D(__d) ((uint32_t)Int_val(__d))
43
44 #define Val_none (Val_int(0))
45
46 #define string_of_option_array(array, index) \
47 ((Field(array, index) == Val_none) ? NULL : String_val(Field(Field(array, index), 0)))
48
49 /* maybe here we should check the range of the input instead of blindly
50 * casting it to uint32 */
51 #define cpuid_input_of_val(i1, i2, input) \
52 i1 = (uint32_t) Int64_val(Field(input, 0)); \
53 i2 = ((Field(input, 1) == Val_none) ? 0xffffffff : (uint32_t) Int64_val(Field(Field(input, 1), 0)));
54
failwith_xc(xc_interface * xch)55 static void Noreturn failwith_xc(xc_interface *xch)
56 {
57 char error_str[1028];
58 if (xch) {
59 const xc_error *error = xc_get_last_error(xch);
60 if (error->code == XC_ERROR_NONE)
61 snprintf(error_str, sizeof(error_str),
62 "%d: %s", errno, strerror(errno));
63 else
64 snprintf(error_str, sizeof(error_str),
65 "%d: %s: %s", error->code,
66 xc_error_code_to_desc(error->code),
67 error->message);
68 } else {
69 snprintf(error_str, sizeof(error_str),
70 "Unable to open XC interface");
71 }
72 caml_raise_with_string(*caml_named_value("xc.error"), error_str);
73 }
74
stub_sizeof_core_header(value unit)75 CAMLprim value stub_sizeof_core_header(value unit)
76 {
77 CAMLparam1(unit);
78 CAMLreturn(Val_int(sizeof(struct xc_core_header)));
79 }
80
stub_sizeof_vcpu_guest_context(value unit)81 CAMLprim value stub_sizeof_vcpu_guest_context(value unit)
82 {
83 CAMLparam1(unit);
84 CAMLreturn(Val_int(sizeof(struct vcpu_guest_context)));
85 }
86
stub_sizeof_xen_pfn(value unit)87 CAMLprim value stub_sizeof_xen_pfn(value unit)
88 {
89 CAMLparam1(unit);
90 CAMLreturn(Val_int(sizeof(xen_pfn_t)));
91 }
92
93 #define XC_CORE_MAGIC 0xF00FEBED
94 #define XC_CORE_MAGIC_HVM 0xF00FEBEE
95
stub_marshall_core_header(value header)96 CAMLprim value stub_marshall_core_header(value header)
97 {
98 CAMLparam1(header);
99 CAMLlocal1(s);
100 struct xc_core_header c_header;
101
102 c_header.xch_magic = (Field(header, 0))
103 ? XC_CORE_MAGIC
104 : XC_CORE_MAGIC_HVM;
105 c_header.xch_nr_vcpus = Int_val(Field(header, 1));
106 c_header.xch_nr_pages = Nativeint_val(Field(header, 2));
107 c_header.xch_ctxt_offset = Int64_val(Field(header, 3));
108 c_header.xch_index_offset = Int64_val(Field(header, 4));
109 c_header.xch_pages_offset = Int64_val(Field(header, 5));
110
111 s = caml_alloc_string(sizeof(c_header));
112 memcpy(String_val(s), (char *) &c_header, sizeof(c_header));
113 CAMLreturn(s);
114 }
115
stub_xc_interface_open(void)116 CAMLprim value stub_xc_interface_open(void)
117 {
118 CAMLparam0();
119 xc_interface *xch;
120
121 /* Don't assert XC_OPENFLAG_NON_REENTRANT because these bindings
122 * do not prevent re-entrancy to libxc */
123 xch = xc_interface_open(NULL, NULL, 0);
124 if (xch == NULL)
125 failwith_xc(NULL);
126 CAMLreturn((value)xch);
127 }
128
129
stub_xc_interface_close(value xch)130 CAMLprim value stub_xc_interface_close(value xch)
131 {
132 CAMLparam1(xch);
133
134 caml_enter_blocking_section();
135 xc_interface_close(_H(xch));
136 caml_leave_blocking_section();
137
138 CAMLreturn(Val_unit);
139 }
140
141 static int domain_create_flag_table[] = {
142 XEN_DOMCTL_CDF_hvm_guest,
143 XEN_DOMCTL_CDF_hap,
144 };
145
stub_xc_domain_create(value xch,value ssidref,value flags,value handle,value domconfig)146 CAMLprim value stub_xc_domain_create(value xch, value ssidref,
147 value flags, value handle,
148 value domconfig)
149 {
150 CAMLparam4(xch, ssidref, flags, handle);
151
152 uint32_t domid = 0;
153 xen_domain_handle_t h = { 0 };
154 int result;
155 int i;
156 uint32_t c_ssidref = Int32_val(ssidref);
157 unsigned int c_flags = 0;
158 value l;
159 xc_domain_configuration_t config = {};
160
161 if (Wosize_val(handle) != 16)
162 caml_invalid_argument("Handle not a 16-integer array");
163
164 for (i = 0; i < sizeof(h); i++) {
165 h[i] = Int_val(Field(handle, i)) & 0xff;
166 }
167
168 for (l = flags; l != Val_none; l = Field(l, 1)) {
169 int v = Int_val(Field(l, 0));
170 c_flags |= domain_create_flag_table[v];
171 }
172
173 switch(Tag_val(domconfig)) {
174 case 0: /* ARM - nothing to do */
175 caml_failwith("Unhandled: ARM");
176 break;
177
178 case 1: /* X86 - emulation flags in the block */
179 for (l = Field(Field(domconfig, 0), 0);
180 l != Val_none;
181 l = Field(l, 1))
182 config.emulation_flags |= 1u << Int_val(Field(l, 0));
183 break;
184
185 default:
186 caml_failwith("Unhandled domconfig type");
187 }
188
189 caml_enter_blocking_section();
190 result = xc_domain_create(_H(xch), c_ssidref, h, c_flags, &domid, &config);
191 caml_leave_blocking_section();
192
193 if (result < 0)
194 failwith_xc(_H(xch));
195
196 CAMLreturn(Val_int(domid));
197 }
198
stub_xc_domain_max_vcpus(value xch,value domid,value max_vcpus)199 CAMLprim value stub_xc_domain_max_vcpus(value xch, value domid,
200 value max_vcpus)
201 {
202 CAMLparam3(xch, domid, max_vcpus);
203 int r;
204
205 r = xc_domain_max_vcpus(_H(xch), _D(domid), Int_val(max_vcpus));
206 if (r)
207 failwith_xc(_H(xch));
208
209 CAMLreturn(Val_unit);
210 }
211
212
stub_xc_domain_sethandle(value xch,value domid,value handle)213 value stub_xc_domain_sethandle(value xch, value domid, value handle)
214 {
215 CAMLparam3(xch, domid, handle);
216 xen_domain_handle_t h = { 0 };
217 int i;
218
219 if (Wosize_val(handle) != 16)
220 caml_invalid_argument("Handle not a 16-integer array");
221
222 for (i = 0; i < sizeof(h); i++) {
223 h[i] = Int_val(Field(handle, i)) & 0xff;
224 }
225
226 i = xc_domain_sethandle(_H(xch), _D(domid), h);
227 if (i)
228 failwith_xc(_H(xch));
229
230 CAMLreturn(Val_unit);
231 }
232
dom_op(value xch,value domid,int (* fn)(xc_interface *,uint32_t))233 static value dom_op(value xch, value domid, int (*fn)(xc_interface *, uint32_t))
234 {
235 CAMLparam2(xch, domid);
236 int result;
237
238 uint32_t c_domid = _D(domid);
239
240 caml_enter_blocking_section();
241 result = fn(_H(xch), c_domid);
242 caml_leave_blocking_section();
243 if (result)
244 failwith_xc(_H(xch));
245 CAMLreturn(Val_unit);
246 }
247
stub_xc_domain_pause(value xch,value domid)248 CAMLprim value stub_xc_domain_pause(value xch, value domid)
249 {
250 return dom_op(xch, domid, xc_domain_pause);
251 }
252
253
stub_xc_domain_unpause(value xch,value domid)254 CAMLprim value stub_xc_domain_unpause(value xch, value domid)
255 {
256 return dom_op(xch, domid, xc_domain_unpause);
257 }
258
stub_xc_domain_destroy(value xch,value domid)259 CAMLprim value stub_xc_domain_destroy(value xch, value domid)
260 {
261 return dom_op(xch, domid, xc_domain_destroy);
262 }
263
stub_xc_domain_resume_fast(value xch,value domid)264 CAMLprim value stub_xc_domain_resume_fast(value xch, value domid)
265 {
266 CAMLparam2(xch, domid);
267 int result;
268
269 uint32_t c_domid = _D(domid);
270
271 caml_enter_blocking_section();
272 result = xc_domain_resume(_H(xch), c_domid, 1);
273 caml_leave_blocking_section();
274 if (result)
275 failwith_xc(_H(xch));
276 CAMLreturn(Val_unit);
277 }
278
stub_xc_domain_shutdown(value xch,value domid,value reason)279 CAMLprim value stub_xc_domain_shutdown(value xch, value domid, value reason)
280 {
281 CAMLparam3(xch, domid, reason);
282 int ret;
283
284 ret = xc_domain_shutdown(_H(xch), _D(domid), Int_val(reason));
285 if (ret < 0)
286 failwith_xc(_H(xch));
287
288 CAMLreturn(Val_unit);
289 }
290
alloc_domaininfo(xc_domaininfo_t * info)291 static value alloc_domaininfo(xc_domaininfo_t * info)
292 {
293 CAMLparam0();
294 CAMLlocal5(result, tmp, arch_config, x86_arch_config, emul_list);
295 int i;
296
297 result = caml_alloc_tuple(17);
298
299 Store_field(result, 0, Val_int(info->domain));
300 Store_field(result, 1, Val_bool(info->flags & XEN_DOMINF_dying));
301 Store_field(result, 2, Val_bool(info->flags & XEN_DOMINF_shutdown));
302 Store_field(result, 3, Val_bool(info->flags & XEN_DOMINF_paused));
303 Store_field(result, 4, Val_bool(info->flags & XEN_DOMINF_blocked));
304 Store_field(result, 5, Val_bool(info->flags & XEN_DOMINF_running));
305 Store_field(result, 6, Val_bool(info->flags & XEN_DOMINF_hvm_guest));
306 Store_field(result, 7, Val_int((info->flags >> XEN_DOMINF_shutdownshift)
307 & XEN_DOMINF_shutdownmask));
308 Store_field(result, 8, caml_copy_nativeint(info->tot_pages));
309 Store_field(result, 9, caml_copy_nativeint(info->max_pages));
310 Store_field(result, 10, caml_copy_int64(info->shared_info_frame));
311 Store_field(result, 11, caml_copy_int64(info->cpu_time));
312 Store_field(result, 12, Val_int(info->nr_online_vcpus));
313 Store_field(result, 13, Val_int(info->max_vcpu_id));
314 Store_field(result, 14, caml_copy_int32(info->ssidref));
315
316 tmp = caml_alloc_small(16, 0);
317 for (i = 0; i < 16; i++) {
318 Field(tmp, i) = Val_int(info->handle[i]);
319 }
320
321 Store_field(result, 15, tmp);
322
323 /* emulation_flags: x86_arch_emulation_flags list; */
324 tmp = emul_list = Val_emptylist;
325 for (i = 0; i < 10; i++) {
326 if ((info->arch_config.emulation_flags >> i) & 1) {
327 tmp = caml_alloc_small(2, Tag_cons);
328 Field(tmp, 0) = Val_int(i);
329 Field(tmp, 1) = emul_list;
330 emul_list = tmp;
331 }
332 }
333
334 /* xen_x86_arch_domainconfig */
335 x86_arch_config = caml_alloc_tuple(1);
336 Store_field(x86_arch_config, 0, emul_list);
337
338 /* arch_config: arch_domainconfig */
339 arch_config = caml_alloc_small(1, 1);
340
341 Store_field(arch_config, 0, x86_arch_config);
342
343 Store_field(result, 16, arch_config);
344
345 CAMLreturn(result);
346 }
347
stub_xc_domain_getinfolist(value xch,value first_domain,value nb)348 CAMLprim value stub_xc_domain_getinfolist(value xch, value first_domain, value nb)
349 {
350 CAMLparam3(xch, first_domain, nb);
351 CAMLlocal2(result, temp);
352 xc_domaininfo_t * info;
353 int i, ret, toalloc, retval;
354 unsigned int c_max_domains;
355 uint32_t c_first_domain;
356
357 /* get the minimum number of allocate byte we need and bump it up to page boundary */
358 toalloc = (sizeof(xc_domaininfo_t) * Int_val(nb)) | 0xfff;
359 ret = posix_memalign((void **) ((void *) &info), 4096, toalloc);
360 if (ret)
361 caml_raise_out_of_memory();
362
363 result = temp = Val_emptylist;
364
365 c_first_domain = _D(first_domain);
366 c_max_domains = Int_val(nb);
367 caml_enter_blocking_section();
368 retval = xc_domain_getinfolist(_H(xch), c_first_domain,
369 c_max_domains, info);
370 caml_leave_blocking_section();
371
372 if (retval < 0) {
373 free(info);
374 failwith_xc(_H(xch));
375 }
376 for (i = 0; i < retval; i++) {
377 result = caml_alloc_small(2, Tag_cons);
378 Field(result, 0) = Val_int(0);
379 Field(result, 1) = temp;
380 temp = result;
381
382 Store_field(result, 0, alloc_domaininfo(info + i));
383 }
384
385 free(info);
386 CAMLreturn(result);
387 }
388
stub_xc_domain_getinfo(value xch,value domid)389 CAMLprim value stub_xc_domain_getinfo(value xch, value domid)
390 {
391 CAMLparam2(xch, domid);
392 CAMLlocal1(result);
393 xc_domaininfo_t info;
394 int ret;
395
396 ret = xc_domain_getinfolist(_H(xch), _D(domid), 1, &info);
397 if (ret != 1)
398 failwith_xc(_H(xch));
399 if (info.domain != _D(domid))
400 failwith_xc(_H(xch));
401
402 result = alloc_domaininfo(&info);
403 CAMLreturn(result);
404 }
405
stub_xc_vcpu_getinfo(value xch,value domid,value vcpu)406 CAMLprim value stub_xc_vcpu_getinfo(value xch, value domid, value vcpu)
407 {
408 CAMLparam3(xch, domid, vcpu);
409 CAMLlocal1(result);
410 xc_vcpuinfo_t info;
411 int retval;
412
413 uint32_t c_domid = _D(domid);
414 uint32_t c_vcpu = Int_val(vcpu);
415 caml_enter_blocking_section();
416 retval = xc_vcpu_getinfo(_H(xch), c_domid,
417 c_vcpu, &info);
418 caml_leave_blocking_section();
419 if (retval < 0)
420 failwith_xc(_H(xch));
421
422 result = caml_alloc_tuple(5);
423 Store_field(result, 0, Val_bool(info.online));
424 Store_field(result, 1, Val_bool(info.blocked));
425 Store_field(result, 2, Val_bool(info.running));
426 Store_field(result, 3, caml_copy_int64(info.cpu_time));
427 Store_field(result, 4, caml_copy_int32(info.cpu));
428
429 CAMLreturn(result);
430 }
431
stub_xc_vcpu_context_get(value xch,value domid,value cpu)432 CAMLprim value stub_xc_vcpu_context_get(value xch, value domid,
433 value cpu)
434 {
435 CAMLparam3(xch, domid, cpu);
436 CAMLlocal1(context);
437 int ret;
438 vcpu_guest_context_any_t ctxt;
439
440 ret = xc_vcpu_getcontext(_H(xch), _D(domid), Int_val(cpu), &ctxt);
441
442 context = caml_alloc_string(sizeof(ctxt));
443 memcpy(String_val(context), (char *) &ctxt.c, sizeof(ctxt.c));
444
445 CAMLreturn(context);
446 }
447
get_cpumap_len(value xch,value cpumap)448 static int get_cpumap_len(value xch, value cpumap)
449 {
450 int ml_len = Wosize_val(cpumap);
451 int xc_len = xc_get_max_cpus(_H(xch));
452
453 if (ml_len < xc_len)
454 return ml_len;
455 else
456 return xc_len;
457 }
458
stub_xc_vcpu_setaffinity(value xch,value domid,value vcpu,value cpumap)459 CAMLprim value stub_xc_vcpu_setaffinity(value xch, value domid,
460 value vcpu, value cpumap)
461 {
462 CAMLparam4(xch, domid, vcpu, cpumap);
463 int i, len = get_cpumap_len(xch, cpumap);
464 xc_cpumap_t c_cpumap;
465 int retval;
466
467 c_cpumap = xc_cpumap_alloc(_H(xch));
468 if (c_cpumap == NULL)
469 failwith_xc(_H(xch));
470
471 for (i=0; i<len; i++) {
472 if (Bool_val(Field(cpumap, i)))
473 c_cpumap[i/8] |= 1 << (i&7);
474 }
475 retval = xc_vcpu_setaffinity(_H(xch), _D(domid),
476 Int_val(vcpu),
477 c_cpumap, NULL,
478 XEN_VCPUAFFINITY_HARD);
479 free(c_cpumap);
480
481 if (retval < 0)
482 failwith_xc(_H(xch));
483 CAMLreturn(Val_unit);
484 }
485
stub_xc_vcpu_getaffinity(value xch,value domid,value vcpu)486 CAMLprim value stub_xc_vcpu_getaffinity(value xch, value domid,
487 value vcpu)
488 {
489 CAMLparam3(xch, domid, vcpu);
490 CAMLlocal1(ret);
491 xc_cpumap_t c_cpumap;
492 int i, len = xc_get_max_cpus(_H(xch));
493 int retval;
494
495 if (len < 1)
496 failwith_xc(_H(xch));
497
498 c_cpumap = xc_cpumap_alloc(_H(xch));
499 if (c_cpumap == NULL)
500 failwith_xc(_H(xch));
501
502 retval = xc_vcpu_getaffinity(_H(xch), _D(domid),
503 Int_val(vcpu),
504 c_cpumap, NULL,
505 XEN_VCPUAFFINITY_HARD);
506 if (retval < 0) {
507 free(c_cpumap);
508 failwith_xc(_H(xch));
509 }
510
511 ret = caml_alloc(len, 0);
512
513 for (i=0; i<len; i++) {
514 if (c_cpumap[i/8] & 1 << (i&7))
515 Store_field(ret, i, Val_true);
516 else
517 Store_field(ret, i, Val_false);
518 }
519
520 free(c_cpumap);
521
522 CAMLreturn(ret);
523 }
524
stub_xc_sched_id(value xch)525 CAMLprim value stub_xc_sched_id(value xch)
526 {
527 CAMLparam1(xch);
528 int sched_id;
529
530 if (xc_sched_id(_H(xch), &sched_id))
531 failwith_xc(_H(xch));
532 CAMLreturn(Val_int(sched_id));
533 }
534
stub_xc_evtchn_alloc_unbound(value xch,value local_domid,value remote_domid)535 CAMLprim value stub_xc_evtchn_alloc_unbound(value xch,
536 value local_domid,
537 value remote_domid)
538 {
539 CAMLparam3(xch, local_domid, remote_domid);
540 int result;
541
542 uint32_t c_local_domid = _D(local_domid);
543 uint32_t c_remote_domid = _D(remote_domid);
544
545 caml_enter_blocking_section();
546 result = xc_evtchn_alloc_unbound(_H(xch), c_local_domid,
547 c_remote_domid);
548 caml_leave_blocking_section();
549
550 if (result < 0)
551 failwith_xc(_H(xch));
552 CAMLreturn(Val_int(result));
553 }
554
stub_xc_evtchn_reset(value xch,value domid)555 CAMLprim value stub_xc_evtchn_reset(value xch, value domid)
556 {
557 CAMLparam2(xch, domid);
558 int r;
559
560 r = xc_evtchn_reset(_H(xch), _D(domid));
561 if (r < 0)
562 failwith_xc(_H(xch));
563 CAMLreturn(Val_unit);
564 }
565
566
stub_xc_readconsolering(value xch)567 CAMLprim value stub_xc_readconsolering(value xch)
568 {
569 /* Safe to use outside of blocking sections because of Ocaml GC lock. */
570 static unsigned int conring_size = 16384 + 1;
571
572 unsigned int count = conring_size, size = count, index = 0;
573 char *str = NULL, *ptr;
574 int ret;
575
576 CAMLparam1(xch);
577 CAMLlocal1(ring);
578
579 str = malloc(size);
580 if (!str)
581 caml_raise_out_of_memory();
582
583 /* Hopefully our conring_size guess is sufficient */
584 caml_enter_blocking_section();
585 ret = xc_readconsolering(_H(xch), str, &count, 0, 0, &index);
586 caml_leave_blocking_section();
587
588 if (ret < 0) {
589 free(str);
590 failwith_xc(_H(xch));
591 }
592
593 while (count == size && ret >= 0) {
594 size += count - 1;
595 if (size < count)
596 break;
597
598 ptr = realloc(str, size);
599 if (!ptr)
600 break;
601
602 str = ptr + count;
603 count = size - count;
604
605 caml_enter_blocking_section();
606 ret = xc_readconsolering(_H(xch), str, &count, 0, 1, &index);
607 caml_leave_blocking_section();
608
609 count += str - ptr;
610 str = ptr;
611 }
612
613 /*
614 * If we didn't break because of an overflow with size, and we have
615 * needed to realloc() ourself more space, update our tracking of the
616 * real console ring size.
617 */
618 if (size > conring_size)
619 conring_size = size;
620
621 ring = caml_alloc_string(count);
622 memcpy(String_val(ring), str, count);
623 free(str);
624
625 CAMLreturn(ring);
626 }
627
stub_xc_send_debug_keys(value xch,value keys)628 CAMLprim value stub_xc_send_debug_keys(value xch, value keys)
629 {
630 CAMLparam2(xch, keys);
631 int r;
632
633 r = xc_send_debug_keys(_H(xch), String_val(keys));
634 if (r)
635 failwith_xc(_H(xch));
636 CAMLreturn(Val_unit);
637 }
638
stub_xc_physinfo(value xch)639 CAMLprim value stub_xc_physinfo(value xch)
640 {
641 CAMLparam1(xch);
642 CAMLlocal3(physinfo, cap_list, tmp);
643 xc_physinfo_t c_physinfo;
644 int r;
645
646 caml_enter_blocking_section();
647 r = xc_physinfo(_H(xch), &c_physinfo);
648 caml_leave_blocking_section();
649
650 if (r)
651 failwith_xc(_H(xch));
652
653 tmp = cap_list = Val_emptylist;
654 for (r = 0; r < 2; r++) {
655 if ((c_physinfo.capabilities >> r) & 1) {
656 tmp = caml_alloc_small(2, Tag_cons);
657 Field(tmp, 0) = Val_int(r);
658 Field(tmp, 1) = cap_list;
659 cap_list = tmp;
660 }
661 }
662
663 physinfo = caml_alloc_tuple(10);
664 Store_field(physinfo, 0, Val_int(c_physinfo.threads_per_core));
665 Store_field(physinfo, 1, Val_int(c_physinfo.cores_per_socket));
666 Store_field(physinfo, 2, Val_int(c_physinfo.nr_cpus));
667 Store_field(physinfo, 3, Val_int(c_physinfo.max_node_id));
668 Store_field(physinfo, 4, Val_int(c_physinfo.cpu_khz));
669 Store_field(physinfo, 5, caml_copy_nativeint(c_physinfo.total_pages));
670 Store_field(physinfo, 6, caml_copy_nativeint(c_physinfo.free_pages));
671 Store_field(physinfo, 7, caml_copy_nativeint(c_physinfo.scrub_pages));
672 Store_field(physinfo, 8, cap_list);
673 Store_field(physinfo, 9, Val_int(c_physinfo.max_cpu_id + 1));
674
675 CAMLreturn(physinfo);
676 }
677
stub_xc_pcpu_info(value xch,value nr_cpus)678 CAMLprim value stub_xc_pcpu_info(value xch, value nr_cpus)
679 {
680 CAMLparam2(xch, nr_cpus);
681 CAMLlocal2(pcpus, v);
682 xc_cpuinfo_t *info;
683 int r, size;
684
685 if (Int_val(nr_cpus) < 1)
686 caml_invalid_argument("nr_cpus");
687
688 info = calloc(Int_val(nr_cpus) + 1, sizeof(*info));
689 if (!info)
690 caml_raise_out_of_memory();
691
692 caml_enter_blocking_section();
693 r = xc_getcpuinfo(_H(xch), Int_val(nr_cpus), info, &size);
694 caml_leave_blocking_section();
695
696 if (r) {
697 free(info);
698 failwith_xc(_H(xch));
699 }
700
701 if (size > 0) {
702 int i;
703 pcpus = caml_alloc(size, 0);
704 for (i = 0; i < size; i++) {
705 v = caml_copy_int64(info[i].idletime);
706 caml_modify(&Field(pcpus, i), v);
707 }
708 } else
709 pcpus = Atom(0);
710 free(info);
711 CAMLreturn(pcpus);
712 }
713
stub_xc_domain_setmaxmem(value xch,value domid,value max_memkb)714 CAMLprim value stub_xc_domain_setmaxmem(value xch, value domid,
715 value max_memkb)
716 {
717 CAMLparam3(xch, domid, max_memkb);
718 int retval;
719
720 uint32_t c_domid = _D(domid);
721 unsigned int c_max_memkb = Int64_val(max_memkb);
722 caml_enter_blocking_section();
723 retval = xc_domain_setmaxmem(_H(xch), c_domid,
724 c_max_memkb);
725 caml_leave_blocking_section();
726 if (retval)
727 failwith_xc(_H(xch));
728 CAMLreturn(Val_unit);
729 }
730
stub_xc_domain_set_memmap_limit(value xch,value domid,value map_limitkb)731 CAMLprim value stub_xc_domain_set_memmap_limit(value xch, value domid,
732 value map_limitkb)
733 {
734 CAMLparam3(xch, domid, map_limitkb);
735 unsigned long v;
736 int retval;
737
738 v = Int64_val(map_limitkb);
739 retval = xc_domain_set_memmap_limit(_H(xch), _D(domid), v);
740 if (retval)
741 failwith_xc(_H(xch));
742
743 CAMLreturn(Val_unit);
744 }
745
stub_xc_domain_memory_increase_reservation(value xch,value domid,value mem_kb)746 CAMLprim value stub_xc_domain_memory_increase_reservation(value xch,
747 value domid,
748 value mem_kb)
749 {
750 CAMLparam3(xch, domid, mem_kb);
751 int retval;
752
753 unsigned long nr_extents = ((unsigned long)(Int64_val(mem_kb))) >> (PAGE_SHIFT - 10);
754
755 uint32_t c_domid = _D(domid);
756 caml_enter_blocking_section();
757 retval = xc_domain_increase_reservation_exact(_H(xch), c_domid,
758 nr_extents, 0, 0, NULL);
759 caml_leave_blocking_section();
760
761 if (retval)
762 failwith_xc(_H(xch));
763 CAMLreturn(Val_unit);
764 }
765
stub_xc_domain_set_machine_address_size(value xch,value domid,value width)766 CAMLprim value stub_xc_domain_set_machine_address_size(value xch,
767 value domid,
768 value width)
769 {
770 CAMLparam3(xch, domid, width);
771 uint32_t c_domid = _D(domid);
772 int c_width = Int_val(width);
773
774 int retval = xc_domain_set_machine_address_size(_H(xch), c_domid, c_width);
775 if (retval)
776 failwith_xc(_H(xch));
777 CAMLreturn(Val_unit);
778 }
779
stub_xc_domain_get_machine_address_size(value xch,value domid)780 CAMLprim value stub_xc_domain_get_machine_address_size(value xch,
781 value domid)
782 {
783 CAMLparam2(xch, domid);
784 int retval;
785
786 retval = xc_domain_get_machine_address_size(_H(xch), _D(domid));
787 if (retval < 0)
788 failwith_xc(_H(xch));
789 CAMLreturn(Val_int(retval));
790 }
791
stub_xc_domain_cpuid_set(value xch,value domid,value input,value config)792 CAMLprim value stub_xc_domain_cpuid_set(value xch, value domid,
793 value input,
794 value config)
795 {
796 CAMLparam4(xch, domid, input, config);
797 CAMLlocal2(array, tmp);
798 #if defined(__i386__) || defined(__x86_64__)
799 int r;
800 unsigned int c_input[2];
801 char *c_config[4], *out_config[4];
802
803 c_config[0] = string_of_option_array(config, 0);
804 c_config[1] = string_of_option_array(config, 1);
805 c_config[2] = string_of_option_array(config, 2);
806 c_config[3] = string_of_option_array(config, 3);
807
808 cpuid_input_of_val(c_input[0], c_input[1], input);
809
810 array = caml_alloc(4, 0);
811 for (r = 0; r < 4; r++) {
812 tmp = Val_none;
813 if (c_config[r]) {
814 tmp = caml_alloc_small(1, 0);
815 Field(tmp, 0) = caml_alloc_string(32);
816 }
817 Store_field(array, r, tmp);
818 }
819
820 for (r = 0; r < 4; r++)
821 out_config[r] = (c_config[r]) ? String_val(Field(Field(array, r), 0)) : NULL;
822
823 r = xc_cpuid_set(_H(xch), _D(domid),
824 c_input, (const char **)c_config, out_config);
825 if (r < 0)
826 failwith_xc(_H(xch));
827 #else
828 caml_failwith("xc_domain_cpuid_set: not implemented");
829 #endif
830 CAMLreturn(array);
831 }
832
stub_xc_domain_cpuid_apply_policy(value xch,value domid)833 CAMLprim value stub_xc_domain_cpuid_apply_policy(value xch, value domid)
834 {
835 CAMLparam2(xch, domid);
836 #if defined(__i386__) || defined(__x86_64__)
837 int r;
838
839 r = xc_cpuid_apply_policy(_H(xch), _D(domid), NULL, 0);
840 if (r < 0)
841 failwith_xc(_H(xch));
842 #else
843 caml_failwith("xc_domain_cpuid_apply_policy: not implemented");
844 #endif
845 CAMLreturn(Val_unit);
846 }
847
stub_xc_version_version(value xch)848 CAMLprim value stub_xc_version_version(value xch)
849 {
850 CAMLparam1(xch);
851 CAMLlocal1(result);
852 xen_extraversion_t extra;
853 long packed;
854 int retval;
855
856 caml_enter_blocking_section();
857 packed = xc_version(_H(xch), XENVER_version, NULL);
858 caml_leave_blocking_section();
859
860 if (packed < 0)
861 failwith_xc(_H(xch));
862
863 caml_enter_blocking_section();
864 retval = xc_version(_H(xch), XENVER_extraversion, &extra);
865 caml_leave_blocking_section();
866
867 if (retval)
868 failwith_xc(_H(xch));
869
870 result = caml_alloc_tuple(3);
871
872 Store_field(result, 0, Val_int(packed >> 16));
873 Store_field(result, 1, Val_int(packed & 0xffff));
874 Store_field(result, 2, caml_copy_string(extra));
875
876 CAMLreturn(result);
877 }
878
879
stub_xc_version_compile_info(value xch)880 CAMLprim value stub_xc_version_compile_info(value xch)
881 {
882 CAMLparam1(xch);
883 CAMLlocal1(result);
884 xen_compile_info_t ci;
885 int retval;
886
887 caml_enter_blocking_section();
888 retval = xc_version(_H(xch), XENVER_compile_info, &ci);
889 caml_leave_blocking_section();
890
891 if (retval)
892 failwith_xc(_H(xch));
893
894 result = caml_alloc_tuple(4);
895
896 Store_field(result, 0, caml_copy_string(ci.compiler));
897 Store_field(result, 1, caml_copy_string(ci.compile_by));
898 Store_field(result, 2, caml_copy_string(ci.compile_domain));
899 Store_field(result, 3, caml_copy_string(ci.compile_date));
900
901 CAMLreturn(result);
902 }
903
904
xc_version_single_string(value xch,int code,void * info)905 static value xc_version_single_string(value xch, int code, void *info)
906 {
907 CAMLparam1(xch);
908 int retval;
909
910 caml_enter_blocking_section();
911 retval = xc_version(_H(xch), code, info);
912 caml_leave_blocking_section();
913
914 if (retval)
915 failwith_xc(_H(xch));
916
917 CAMLreturn(caml_copy_string((char *)info));
918 }
919
920
stub_xc_version_changeset(value xch)921 CAMLprim value stub_xc_version_changeset(value xch)
922 {
923 xen_changeset_info_t ci;
924
925 return xc_version_single_string(xch, XENVER_changeset, &ci);
926 }
927
928
stub_xc_version_capabilities(value xch)929 CAMLprim value stub_xc_version_capabilities(value xch)
930 {
931 xen_capabilities_info_t ci;
932
933 return xc_version_single_string(xch, XENVER_capabilities, &ci);
934 }
935
936
stub_pages_to_kib(value pages)937 CAMLprim value stub_pages_to_kib(value pages)
938 {
939 CAMLparam1(pages);
940
941 CAMLreturn(caml_copy_int64(Int64_val(pages) << (PAGE_SHIFT - 10)));
942 }
943
944
stub_map_foreign_range(value xch,value dom,value size,value mfn)945 CAMLprim value stub_map_foreign_range(value xch, value dom,
946 value size, value mfn)
947 {
948 CAMLparam4(xch, dom, size, mfn);
949 CAMLlocal1(result);
950 struct mmap_interface *intf;
951 uint32_t c_dom;
952 unsigned long c_mfn;
953
954 result = caml_alloc(sizeof(struct mmap_interface), Abstract_tag);
955 intf = (struct mmap_interface *) result;
956
957 intf->len = Int_val(size);
958
959 c_dom = _D(dom);
960 c_mfn = Nativeint_val(mfn);
961 caml_enter_blocking_section();
962 intf->addr = xc_map_foreign_range(_H(xch), c_dom,
963 intf->len, PROT_READ|PROT_WRITE,
964 c_mfn);
965 caml_leave_blocking_section();
966 if (!intf->addr)
967 caml_failwith("xc_map_foreign_range error");
968 CAMLreturn(result);
969 }
970
stub_sched_credit_domain_get(value xch,value domid)971 CAMLprim value stub_sched_credit_domain_get(value xch, value domid)
972 {
973 CAMLparam2(xch, domid);
974 CAMLlocal1(sdom);
975 struct xen_domctl_sched_credit c_sdom;
976 int ret;
977
978 caml_enter_blocking_section();
979 ret = xc_sched_credit_domain_get(_H(xch), _D(domid), &c_sdom);
980 caml_leave_blocking_section();
981 if (ret != 0)
982 failwith_xc(_H(xch));
983
984 sdom = caml_alloc_tuple(2);
985 Store_field(sdom, 0, Val_int(c_sdom.weight));
986 Store_field(sdom, 1, Val_int(c_sdom.cap));
987
988 CAMLreturn(sdom);
989 }
990
stub_sched_credit_domain_set(value xch,value domid,value sdom)991 CAMLprim value stub_sched_credit_domain_set(value xch, value domid,
992 value sdom)
993 {
994 CAMLparam3(xch, domid, sdom);
995 struct xen_domctl_sched_credit c_sdom;
996 int ret;
997
998 c_sdom.weight = Int_val(Field(sdom, 0));
999 c_sdom.cap = Int_val(Field(sdom, 1));
1000 caml_enter_blocking_section();
1001 ret = xc_sched_credit_domain_set(_H(xch), _D(domid), &c_sdom);
1002 caml_leave_blocking_section();
1003 if (ret != 0)
1004 failwith_xc(_H(xch));
1005
1006 CAMLreturn(Val_unit);
1007 }
1008
stub_shadow_allocation_get(value xch,value domid)1009 CAMLprim value stub_shadow_allocation_get(value xch, value domid)
1010 {
1011 CAMLparam2(xch, domid);
1012 CAMLlocal1(mb);
1013 unsigned long c_mb;
1014 int ret;
1015
1016 caml_enter_blocking_section();
1017 ret = xc_shadow_control(_H(xch), _D(domid),
1018 XEN_DOMCTL_SHADOW_OP_GET_ALLOCATION,
1019 NULL, 0, &c_mb, 0, NULL);
1020 caml_leave_blocking_section();
1021 if (ret != 0)
1022 failwith_xc(_H(xch));
1023
1024 mb = Val_int(c_mb);
1025 CAMLreturn(mb);
1026 }
1027
stub_shadow_allocation_set(value xch,value domid,value mb)1028 CAMLprim value stub_shadow_allocation_set(value xch, value domid,
1029 value mb)
1030 {
1031 CAMLparam3(xch, domid, mb);
1032 unsigned long c_mb;
1033 int ret;
1034
1035 c_mb = Int_val(mb);
1036 caml_enter_blocking_section();
1037 ret = xc_shadow_control(_H(xch), _D(domid),
1038 XEN_DOMCTL_SHADOW_OP_SET_ALLOCATION,
1039 NULL, 0, &c_mb, 0, NULL);
1040 caml_leave_blocking_section();
1041 if (ret != 0)
1042 failwith_xc(_H(xch));
1043
1044 CAMLreturn(Val_unit);
1045 }
1046
stub_xc_domain_get_pfn_list(value xch,value domid,value nr_pfns)1047 CAMLprim value stub_xc_domain_get_pfn_list(value xch, value domid,
1048 value nr_pfns)
1049 {
1050 CAMLparam3(xch, domid, nr_pfns);
1051 CAMLlocal2(array, v);
1052 unsigned long c_nr_pfns;
1053 long ret, i;
1054 uint64_t *c_array;
1055
1056 c_nr_pfns = Nativeint_val(nr_pfns);
1057
1058 c_array = malloc(sizeof(uint64_t) * c_nr_pfns);
1059 if (!c_array)
1060 caml_raise_out_of_memory();
1061
1062 ret = xc_get_pfn_list(_H(xch), _D(domid),
1063 c_array, c_nr_pfns);
1064 if (ret < 0) {
1065 free(c_array);
1066 failwith_xc(_H(xch));
1067 }
1068
1069 array = caml_alloc(ret, 0);
1070 for (i = 0; i < ret; i++) {
1071 v = caml_copy_nativeint(c_array[i]);
1072 Store_field(array, i, v);
1073 }
1074 free(c_array);
1075
1076 CAMLreturn(array);
1077 }
1078
stub_xc_domain_ioport_permission(value xch,value domid,value start_port,value nr_ports,value allow)1079 CAMLprim value stub_xc_domain_ioport_permission(value xch, value domid,
1080 value start_port, value nr_ports,
1081 value allow)
1082 {
1083 CAMLparam5(xch, domid, start_port, nr_ports, allow);
1084 uint32_t c_start_port, c_nr_ports;
1085 uint8_t c_allow;
1086 int ret;
1087
1088 c_start_port = Int_val(start_port);
1089 c_nr_ports = Int_val(nr_ports);
1090 c_allow = Bool_val(allow);
1091
1092 ret = xc_domain_ioport_permission(_H(xch), _D(domid),
1093 c_start_port, c_nr_ports, c_allow);
1094 if (ret < 0)
1095 failwith_xc(_H(xch));
1096
1097 CAMLreturn(Val_unit);
1098 }
1099
stub_xc_domain_iomem_permission(value xch,value domid,value start_pfn,value nr_pfns,value allow)1100 CAMLprim value stub_xc_domain_iomem_permission(value xch, value domid,
1101 value start_pfn, value nr_pfns,
1102 value allow)
1103 {
1104 CAMLparam5(xch, domid, start_pfn, nr_pfns, allow);
1105 unsigned long c_start_pfn, c_nr_pfns;
1106 uint8_t c_allow;
1107 int ret;
1108
1109 c_start_pfn = Nativeint_val(start_pfn);
1110 c_nr_pfns = Nativeint_val(nr_pfns);
1111 c_allow = Bool_val(allow);
1112
1113 ret = xc_domain_iomem_permission(_H(xch), _D(domid),
1114 c_start_pfn, c_nr_pfns, c_allow);
1115 if (ret < 0)
1116 failwith_xc(_H(xch));
1117
1118 CAMLreturn(Val_unit);
1119 }
1120
stub_xc_domain_irq_permission(value xch,value domid,value pirq,value allow)1121 CAMLprim value stub_xc_domain_irq_permission(value xch, value domid,
1122 value pirq, value allow)
1123 {
1124 CAMLparam4(xch, domid, pirq, allow);
1125 uint8_t c_pirq;
1126 uint8_t c_allow;
1127 int ret;
1128
1129 c_pirq = Int_val(pirq);
1130 c_allow = Bool_val(allow);
1131
1132 ret = xc_domain_irq_permission(_H(xch), _D(domid),
1133 c_pirq, c_allow);
1134 if (ret < 0)
1135 failwith_xc(_H(xch));
1136
1137 CAMLreturn(Val_unit);
1138 }
1139
encode_sbdf(int domain,int bus,int dev,int func)1140 static uint32_t encode_sbdf(int domain, int bus, int dev, int func)
1141 {
1142 return ((uint32_t)domain & 0xffff) << 16 |
1143 ((uint32_t)bus & 0xff) << 8 |
1144 ((uint32_t)dev & 0x1f) << 3 |
1145 ((uint32_t)func & 0x7);
1146 }
1147
stub_xc_domain_test_assign_device(value xch,value domid,value desc)1148 CAMLprim value stub_xc_domain_test_assign_device(value xch, value domid, value desc)
1149 {
1150 CAMLparam3(xch, domid, desc);
1151 int ret;
1152 int domain, bus, dev, func;
1153 uint32_t sbdf;
1154
1155 domain = Int_val(Field(desc, 0));
1156 bus = Int_val(Field(desc, 1));
1157 dev = Int_val(Field(desc, 2));
1158 func = Int_val(Field(desc, 3));
1159 sbdf = encode_sbdf(domain, bus, dev, func);
1160
1161 ret = xc_test_assign_device(_H(xch), _D(domid), sbdf);
1162
1163 CAMLreturn(Val_bool(ret == 0));
1164 }
1165
1166 static int domain_assign_device_rdm_flag_table[] = {
1167 XEN_DOMCTL_DEV_RDM_RELAXED,
1168 };
1169
stub_xc_domain_assign_device(value xch,value domid,value desc,value rflag)1170 CAMLprim value stub_xc_domain_assign_device(value xch, value domid, value desc,
1171 value rflag)
1172 {
1173 CAMLparam4(xch, domid, desc, rflag);
1174 int ret;
1175 int domain, bus, dev, func;
1176 uint32_t sbdf, flag;
1177
1178 domain = Int_val(Field(desc, 0));
1179 bus = Int_val(Field(desc, 1));
1180 dev = Int_val(Field(desc, 2));
1181 func = Int_val(Field(desc, 3));
1182 sbdf = encode_sbdf(domain, bus, dev, func);
1183
1184 ret = Int_val(Field(rflag, 0));
1185 flag = domain_assign_device_rdm_flag_table[ret];
1186
1187 ret = xc_assign_device(_H(xch), _D(domid), sbdf, flag);
1188
1189 if (ret < 0)
1190 failwith_xc(_H(xch));
1191 CAMLreturn(Val_unit);
1192 }
1193
stub_xc_domain_deassign_device(value xch,value domid,value desc)1194 CAMLprim value stub_xc_domain_deassign_device(value xch, value domid, value desc)
1195 {
1196 CAMLparam3(xch, domid, desc);
1197 int ret;
1198 int domain, bus, dev, func;
1199 uint32_t sbdf;
1200
1201 domain = Int_val(Field(desc, 0));
1202 bus = Int_val(Field(desc, 1));
1203 dev = Int_val(Field(desc, 2));
1204 func = Int_val(Field(desc, 3));
1205 sbdf = encode_sbdf(domain, bus, dev, func);
1206
1207 ret = xc_deassign_device(_H(xch), _D(domid), sbdf);
1208
1209 if (ret < 0)
1210 failwith_xc(_H(xch));
1211 CAMLreturn(Val_unit);
1212 }
1213
stub_xc_get_cpu_featureset(value xch,value idx)1214 CAMLprim value stub_xc_get_cpu_featureset(value xch, value idx)
1215 {
1216 CAMLparam2(xch, idx);
1217 CAMLlocal1(bitmap_val);
1218 #if defined(__i386__) || defined(__x86_64__)
1219
1220 /* Safe, because of the global ocaml lock. */
1221 static uint32_t fs_len;
1222
1223 if (fs_len == 0)
1224 {
1225 int ret = xc_get_cpu_featureset(_H(xch), 0, &fs_len, NULL);
1226
1227 if (ret || (fs_len == 0))
1228 failwith_xc(_H(xch));
1229 }
1230
1231 {
1232 /* To/from hypervisor to retrieve actual featureset */
1233 uint32_t fs[fs_len], len = fs_len;
1234 unsigned int i;
1235
1236 int ret = xc_get_cpu_featureset(_H(xch), Int_val(idx), &len, fs);
1237
1238 if (ret)
1239 failwith_xc(_H(xch));
1240
1241 bitmap_val = caml_alloc(len, 0);
1242
1243 for (i = 0; i < len; ++i)
1244 Store_field(bitmap_val, i, caml_copy_int64(fs[i]));
1245 }
1246 #else
1247 caml_failwith("xc_get_cpu_featureset: not implemented");
1248 #endif
1249 CAMLreturn(bitmap_val);
1250 }
1251
stub_xc_watchdog(value xch,value domid,value timeout)1252 CAMLprim value stub_xc_watchdog(value xch, value domid, value timeout)
1253 {
1254 CAMLparam3(xch, domid, timeout);
1255 int ret;
1256 unsigned int c_timeout = Int32_val(timeout);
1257
1258 ret = xc_watchdog(_H(xch), _D(domid), c_timeout);
1259 if (ret < 0)
1260 failwith_xc(_H(xch));
1261
1262 CAMLreturn(Val_int(ret));
1263 }
1264
1265 /*
1266 * Local variables:
1267 * indent-tabs-mode: t
1268 * c-basic-offset: 8
1269 * tab-width: 8
1270 * End:
1271 */
1272