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