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
17type domid = int
18type vcpuinfo = {
19  online : bool;
20  blocked : bool;
21  running : bool;
22  cputime : int64;
23  cpumap : int32;
24}
25
26type xen_arm_arch_domainconfig = {
27  gic_version: int;
28  nr_spis: int;
29  clock_frequency: int32;
30}
31
32type x86_arch_emulation_flags =
33  | X86_EMU_LAPIC
34  | X86_EMU_HPET
35  | X86_EMU_PM
36  | X86_EMU_RTC
37  | X86_EMU_IOAPIC
38  | X86_EMU_PIC
39  | X86_EMU_VGA
40  | X86_EMU_IOMMU
41  | X86_EMU_PIT
42  | X86_EMU_USE_PIRQ
43  | X86_EMU_VPCI
44
45type x86_arch_misc_flags =
46  | X86_MSR_RELAXED
47
48type xen_x86_arch_domainconfig = {
49  emulation_flags: x86_arch_emulation_flags list;
50  misc_flags: x86_arch_misc_flags list;
51}
52
53type arch_domainconfig =
54  | ARM of xen_arm_arch_domainconfig
55  | X86 of xen_x86_arch_domainconfig
56
57type domain_create_flag =
58  | CDF_HVM
59  | CDF_HAP
60  | CDF_S3_INTEGRITY
61  | CDF_OOS_OFF
62  | CDF_XS_DOMAIN
63  | CDF_IOMMU
64  | CDF_NESTED_VIRT
65  | CDF_VPMU
66
67type domain_create_iommu_opts =
68  | IOMMU_NO_SHAREPT
69
70type domctl_create_config = {
71  ssidref: int32;
72  handle: string;
73  flags: domain_create_flag list;
74  iommu_opts: domain_create_iommu_opts list;
75  max_vcpus: int;
76  max_evtchn_port: int;
77  max_grant_frames: int;
78  max_maptrack_frames: int;
79  max_grant_version: int;
80  vmtrace_buf_kb: int32;
81  cpupool_id: int32;
82  arch: arch_domainconfig;
83}
84
85type domaininfo = {
86  domid : domid;
87  dying : bool;
88  shutdown : bool;
89  paused : bool;
90  blocked : bool;
91  running : bool;
92  hvm_guest : bool;
93  shutdown_code : int;
94  total_memory_pages : nativeint;
95  max_memory_pages : nativeint;
96  shared_info_frame : int64;
97  cpu_time : int64;
98  nr_online_vcpus : int;
99  max_vcpu_id : int;
100  ssidref : int32;
101  handle : int array;
102  arch_config : arch_domainconfig;
103}
104type sched_control = { weight : int; cap : int; }
105type physinfo_cap_flag =
106  | CAP_HVM
107  | CAP_PV
108  | CAP_DirectIO
109  | CAP_HAP
110  | CAP_Shadow
111  | CAP_IOMMU_HAP_PT_SHARE
112  | CAP_Vmtrace
113  | CAP_Vpmu
114  | CAP_Gnttab_v1
115  | CAP_Gnttab_v2
116
117type arm_physinfo_caps =
118  {
119    sve_vl: int;
120  }
121
122type x86_physinfo_cap_flag
123
124type arch_physinfo_cap_flags =
125  | ARM of arm_physinfo_caps
126  | X86 of x86_physinfo_cap_flag list
127
128type physinfo = {
129  threads_per_core : int;
130  cores_per_socket : int;
131  nr_cpus          : int;
132  max_node_id      : int;
133  cpu_khz          : int;
134  total_pages      : nativeint;
135  free_pages       : nativeint;
136  scrub_pages      : nativeint;
137  capabilities     : physinfo_cap_flag list;
138  max_nr_cpus      : int; (** compile-time max possible number of nr_cpus *)
139  arch_capabilities : arch_physinfo_cap_flags;
140}
141type version = { major : int; minor : int; extra : string; }
142type compile_info = {
143  compiler : string;
144  compile_by : string;
145  compile_domain : string;
146  compile_date : string;
147}
148type shutdown_reason = Poweroff | Reboot | Suspend | Crash | Watchdog | Soft_reset
149
150exception Error of string
151type handle
152external interface_open : unit -> handle = "stub_xc_interface_open"
153
154(** [with_intf f] runs [f] with a global handle that is opened on demand
155 * and kept open. Conceptually, a client should use either
156 * interface_open and interface_close or with_intf although mixing both
157 * is possible *)
158val with_intf : (handle -> 'a) -> 'a
159
160(** [get_handle] returns the global handle used by [with_intf] *)
161val get_handle: unit -> handle option
162
163(** [close handle] closes the handle maintained by [with_intf]. This
164 * should only be closed before process exit. It must not be called from
165 * a function called directly or indirectly by with_intf as this
166 * would invalidate the handle that with_intf passes to its argument. *)
167val close_handle: unit -> unit
168
169val domain_create: handle -> ?domid:int -> domctl_create_config -> domid
170
171external domain_sethandle : handle -> domid -> string -> unit = "stub_xc_domain_sethandle"
172external domain_max_vcpus : handle -> domid -> int -> unit
173  = "stub_xc_domain_max_vcpus"
174external domain_pause : handle -> domid -> unit = "stub_xc_domain_pause"
175external domain_unpause : handle -> domid -> unit = "stub_xc_domain_unpause"
176external domain_resume_fast : handle -> domid -> unit
177  = "stub_xc_domain_resume_fast"
178external domain_destroy : handle -> domid -> unit = "stub_xc_domain_destroy"
179external domain_shutdown : handle -> domid -> shutdown_reason -> unit
180  = "stub_xc_domain_shutdown"
181external _domain_getinfolist : handle -> domid -> int -> domaininfo list
182  = "stub_xc_domain_getinfolist"
183val domain_getinfolist : handle -> domid -> domaininfo list
184external domain_getinfo : handle -> domid -> domaininfo
185  = "stub_xc_domain_getinfo"
186external domain_get_vcpuinfo : handle -> int -> int -> vcpuinfo
187  = "stub_xc_vcpu_getinfo"
188external domain_ioport_permission: handle -> domid -> int -> int -> bool -> unit
189  = "stub_xc_domain_ioport_permission"
190external domain_iomem_permission: handle -> domid -> nativeint -> nativeint -> bool -> unit
191  = "stub_xc_domain_iomem_permission"
192external domain_irq_permission: handle -> domid -> int -> bool -> unit
193  = "stub_xc_domain_irq_permission"
194external vcpu_affinity_set : handle -> domid -> int -> bool array -> unit
195  = "stub_xc_vcpu_setaffinity"
196external vcpu_affinity_get : handle -> domid -> int -> bool array
197  = "stub_xc_vcpu_getaffinity"
198external vcpu_context_get : handle -> domid -> int -> string
199  = "stub_xc_vcpu_context_get"
200external sched_id : handle -> int = "stub_xc_sched_id"
201external sched_credit_domain_set : handle -> domid -> sched_control -> unit
202  = "stub_sched_credit_domain_set"
203external sched_credit_domain_get : handle -> domid -> sched_control
204  = "stub_sched_credit_domain_get"
205external shadow_allocation_set : handle -> domid -> int -> unit
206  = "stub_shadow_allocation_set"
207external shadow_allocation_get : handle -> domid -> int
208  = "stub_shadow_allocation_get"
209external evtchn_alloc_unbound : handle -> domid -> domid -> int
210  = "stub_xc_evtchn_alloc_unbound"
211external evtchn_reset : handle -> domid -> unit = "stub_xc_evtchn_reset"
212
213type evtchn_interdomain = { dom: domid; port: int }
214
215type evtchn_stat =
216  | EVTCHNSTAT_unbound of domid
217  | EVTCHNSTAT_interdomain of evtchn_interdomain
218  | EVTCHNSTAT_pirq of int
219  | EVTCHNSTAT_virq of Xeneventchn.virq_t
220  | EVTCHNSTAT_ipi
221
222type evtchn_status = { vcpu: int; status: evtchn_stat }
223
224external evtchn_status: handle -> domid -> int -> evtchn_status option =
225  "stub_xc_evtchn_status"
226
227external readconsolering : handle -> string = "stub_xc_readconsolering"
228external send_debug_keys : handle -> string -> unit = "stub_xc_send_debug_keys"
229external physinfo : handle -> physinfo = "stub_xc_physinfo"
230external pcpu_info: handle -> int -> int64 array = "stub_xc_pcpu_info"
231external domain_setmaxmem : handle -> domid -> int64 -> unit
232  = "stub_xc_domain_setmaxmem"
233external domain_set_memmap_limit : handle -> domid -> int64 -> unit
234  = "stub_xc_domain_set_memmap_limit"
235external domain_memory_increase_reservation :
236  handle -> domid -> int64 -> unit
237  = "stub_xc_domain_memory_increase_reservation"
238external map_foreign_range :
239  handle -> domid -> int -> nativeint -> Xenmmap.mmap_interface
240  = "stub_map_foreign_range"
241
242(* needs to be sorted according to its numeric value, watch out for gaps! *)
243type hvm_param =
244  | HVM_PARAM_CALLBACK_IRQ
245  | HVM_PARAM_STORE_PFN
246  | HVM_PARAM_STORE_EVTCHN
247  | HVM_PARAM_UNDEF_3
248  | HVM_PARAM_PAE_ENABLED
249  | HVM_PARAM_IOREQ_PFN
250  | HVM_PARAM_BUFIOREQ_PFN
251  | HVM_PARAM_UNDEF_7
252  | HVM_PARAM_UNDEF_8
253  | HVM_PARAM_VIRIDIAN
254  | HVM_PARAM_TIMER_MODE
255  | HVM_PARAM_HPET_ENABLED
256  | HVM_PARAM_IDENT_PT
257  | HVM_PARAM_UNDEF_13
258  | HVM_PARAM_ACPI_S_STATE
259  | HVM_PARAM_VM86_TSS
260  | HVM_PARAM_VPT_ALIGN
261  | HVM_PARAM_CONSOLE_PFN
262  | HVM_PARAM_CONSOLE_EVTCHN
263  | HVM_PARAM_ACPI_IOPORTS_LOCATION
264  | HVM_PARAM_MEMORY_EVENT_CR0
265  | HVM_PARAM_MEMORY_EVENT_CR3
266  | HVM_PARAM_MEMORY_EVENT_CR4
267  | HVM_PARAM_MEMORY_EVENT_INT3
268  | HVM_PARAM_NESTEDHVM
269  | HVM_PARAM_MEMORY_EVENT_SINGLE_STEP
270  | HVM_PARAM_UNDEF_26
271  | HVM_PARAM_PAGING_RING_PFN
272  | HVM_PARAM_MONITOR_RING_PFN
273  | HVM_PARAM_SHARING_RING_PFN
274  | HVM_PARAM_MEMORY_EVENT_MSR
275  | HVM_PARAM_TRIPLE_FAULT_REASON
276  | HVM_PARAM_IOREQ_SERVER_PFN
277  | HVM_PARAM_NR_IOREQ_SERVER_PAGES
278  | HVM_PARAM_VM_GENERATION_ID_ADDR
279  | HVM_PARAM_ALTP2M
280  | HVM_PARAM_X87_FIP_WIDTH
281  | HVM_PARAM_VM86_TSS_SIZED
282  | HVM_PARAM_MCA_CAP
283
284external hvm_param_get: handle -> domid -> hvm_param -> int64
285  = "stub_xc_hvm_param_get"
286
287external hvm_param_set: handle -> domid -> hvm_param -> int64 -> unit
288  = "stub_xc_hvm_param_set"
289
290external domain_assign_device: handle -> domid -> (int * int * int * int) -> unit
291  = "stub_xc_domain_assign_device"
292external domain_deassign_device: handle -> domid -> (int * int * int * int) -> unit
293  = "stub_xc_domain_deassign_device"
294external domain_test_assign_device: handle -> domid -> (int * int * int * int) -> bool
295  = "stub_xc_domain_test_assign_device"
296
297external version : handle -> version = "stub_xc_version_version"
298external version_compile_info : handle -> compile_info
299  = "stub_xc_version_compile_info"
300external version_changeset : handle -> string = "stub_xc_version_changeset"
301external version_capabilities : handle -> string
302  = "stub_xc_version_capabilities"
303
304type featureset_index =
305  | Featureset_raw
306  | Featureset_host
307  | Featureset_pv
308  | Featureset_hvm
309  | Featureset_pv_max
310  | Featureset_hvm_max
311external get_cpu_featureset : handle -> featureset_index -> int64 array = "stub_xc_get_cpu_featureset"
312
313external pages_to_kib : int64 -> int64 = "stub_pages_to_kib"
314val pages_to_mib : int64 -> int64
315external watchdog : handle -> int -> int32 -> int
316  = "stub_xc_watchdog"
317