cachepc-qemu

Fork of AMDESE/qemu with changes for cachepc side-channel attack
git clone https://git.sinitax.com/sinitax/cachepc-qemu
Log | Files | Refs | Submodules | LICENSE | sfeed.txt

machine.c (46536B)


      1#include "qemu/osdep.h"
      2#include "cpu.h"
      3#include "exec/exec-all.h"
      4#include "hw/isa/isa.h"
      5#include "migration/cpu.h"
      6#include "kvm/hyperv.h"
      7#include "hw/i386/x86.h"
      8#include "kvm/kvm_i386.h"
      9
     10#include "sysemu/kvm.h"
     11#include "sysemu/tcg.h"
     12
     13#include "qemu/error-report.h"
     14
     15static const VMStateDescription vmstate_segment = {
     16    .name = "segment",
     17    .version_id = 1,
     18    .minimum_version_id = 1,
     19    .fields = (VMStateField[]) {
     20        VMSTATE_UINT32(selector, SegmentCache),
     21        VMSTATE_UINTTL(base, SegmentCache),
     22        VMSTATE_UINT32(limit, SegmentCache),
     23        VMSTATE_UINT32(flags, SegmentCache),
     24        VMSTATE_END_OF_LIST()
     25    }
     26};
     27
     28#define VMSTATE_SEGMENT(_field, _state) {                            \
     29    .name       = (stringify(_field)),                               \
     30    .size       = sizeof(SegmentCache),                              \
     31    .vmsd       = &vmstate_segment,                                  \
     32    .flags      = VMS_STRUCT,                                        \
     33    .offset     = offsetof(_state, _field)                           \
     34            + type_check(SegmentCache,typeof_field(_state, _field))  \
     35}
     36
     37#define VMSTATE_SEGMENT_ARRAY(_field, _state, _n)                    \
     38    VMSTATE_STRUCT_ARRAY(_field, _state, _n, 0, vmstate_segment, SegmentCache)
     39
     40static const VMStateDescription vmstate_xmm_reg = {
     41    .name = "xmm_reg",
     42    .version_id = 1,
     43    .minimum_version_id = 1,
     44    .fields = (VMStateField[]) {
     45        VMSTATE_UINT64(ZMM_Q(0), ZMMReg),
     46        VMSTATE_UINT64(ZMM_Q(1), ZMMReg),
     47        VMSTATE_END_OF_LIST()
     48    }
     49};
     50
     51#define VMSTATE_XMM_REGS(_field, _state, _start)                         \
     52    VMSTATE_STRUCT_SUB_ARRAY(_field, _state, _start, CPU_NB_REGS, 0,     \
     53                             vmstate_xmm_reg, ZMMReg)
     54
     55/* YMMH format is the same as XMM, but for bits 128-255 */
     56static const VMStateDescription vmstate_ymmh_reg = {
     57    .name = "ymmh_reg",
     58    .version_id = 1,
     59    .minimum_version_id = 1,
     60    .fields = (VMStateField[]) {
     61        VMSTATE_UINT64(ZMM_Q(2), ZMMReg),
     62        VMSTATE_UINT64(ZMM_Q(3), ZMMReg),
     63        VMSTATE_END_OF_LIST()
     64    }
     65};
     66
     67#define VMSTATE_YMMH_REGS_VARS(_field, _state, _start, _v)               \
     68    VMSTATE_STRUCT_SUB_ARRAY(_field, _state, _start, CPU_NB_REGS, _v,    \
     69                             vmstate_ymmh_reg, ZMMReg)
     70
     71static const VMStateDescription vmstate_zmmh_reg = {
     72    .name = "zmmh_reg",
     73    .version_id = 1,
     74    .minimum_version_id = 1,
     75    .fields = (VMStateField[]) {
     76        VMSTATE_UINT64(ZMM_Q(4), ZMMReg),
     77        VMSTATE_UINT64(ZMM_Q(5), ZMMReg),
     78        VMSTATE_UINT64(ZMM_Q(6), ZMMReg),
     79        VMSTATE_UINT64(ZMM_Q(7), ZMMReg),
     80        VMSTATE_END_OF_LIST()
     81    }
     82};
     83
     84#define VMSTATE_ZMMH_REGS_VARS(_field, _state, _start)                   \
     85    VMSTATE_STRUCT_SUB_ARRAY(_field, _state, _start, CPU_NB_REGS, 0,     \
     86                             vmstate_zmmh_reg, ZMMReg)
     87
     88#ifdef TARGET_X86_64
     89static const VMStateDescription vmstate_hi16_zmm_reg = {
     90    .name = "hi16_zmm_reg",
     91    .version_id = 1,
     92    .minimum_version_id = 1,
     93    .fields = (VMStateField[]) {
     94        VMSTATE_UINT64(ZMM_Q(0), ZMMReg),
     95        VMSTATE_UINT64(ZMM_Q(1), ZMMReg),
     96        VMSTATE_UINT64(ZMM_Q(2), ZMMReg),
     97        VMSTATE_UINT64(ZMM_Q(3), ZMMReg),
     98        VMSTATE_UINT64(ZMM_Q(4), ZMMReg),
     99        VMSTATE_UINT64(ZMM_Q(5), ZMMReg),
    100        VMSTATE_UINT64(ZMM_Q(6), ZMMReg),
    101        VMSTATE_UINT64(ZMM_Q(7), ZMMReg),
    102        VMSTATE_END_OF_LIST()
    103    }
    104};
    105
    106#define VMSTATE_Hi16_ZMM_REGS_VARS(_field, _state, _start)               \
    107    VMSTATE_STRUCT_SUB_ARRAY(_field, _state, _start, CPU_NB_REGS, 0,     \
    108                             vmstate_hi16_zmm_reg, ZMMReg)
    109#endif
    110
    111static const VMStateDescription vmstate_bnd_regs = {
    112    .name = "bnd_regs",
    113    .version_id = 1,
    114    .minimum_version_id = 1,
    115    .fields = (VMStateField[]) {
    116        VMSTATE_UINT64(lb, BNDReg),
    117        VMSTATE_UINT64(ub, BNDReg),
    118        VMSTATE_END_OF_LIST()
    119    }
    120};
    121
    122#define VMSTATE_BND_REGS(_field, _state, _n)          \
    123    VMSTATE_STRUCT_ARRAY(_field, _state, _n, 0, vmstate_bnd_regs, BNDReg)
    124
    125static const VMStateDescription vmstate_mtrr_var = {
    126    .name = "mtrr_var",
    127    .version_id = 1,
    128    .minimum_version_id = 1,
    129    .fields = (VMStateField[]) {
    130        VMSTATE_UINT64(base, MTRRVar),
    131        VMSTATE_UINT64(mask, MTRRVar),
    132        VMSTATE_END_OF_LIST()
    133    }
    134};
    135
    136#define VMSTATE_MTRR_VARS(_field, _state, _n, _v)                    \
    137    VMSTATE_STRUCT_ARRAY(_field, _state, _n, _v, vmstate_mtrr_var, MTRRVar)
    138
    139typedef struct x86_FPReg_tmp {
    140    FPReg *parent;
    141    uint64_t tmp_mant;
    142    uint16_t tmp_exp;
    143} x86_FPReg_tmp;
    144
    145static void cpu_get_fp80(uint64_t *pmant, uint16_t *pexp, floatx80 f)
    146{
    147    CPU_LDoubleU temp;
    148
    149    temp.d = f;
    150    *pmant = temp.l.lower;
    151    *pexp = temp.l.upper;
    152}
    153
    154static floatx80 cpu_set_fp80(uint64_t mant, uint16_t upper)
    155{
    156    CPU_LDoubleU temp;
    157
    158    temp.l.upper = upper;
    159    temp.l.lower = mant;
    160    return temp.d;
    161}
    162
    163static int fpreg_pre_save(void *opaque)
    164{
    165    x86_FPReg_tmp *tmp = opaque;
    166
    167    /* we save the real CPU data (in case of MMX usage only 'mant'
    168       contains the MMX register */
    169    cpu_get_fp80(&tmp->tmp_mant, &tmp->tmp_exp, tmp->parent->d);
    170
    171    return 0;
    172}
    173
    174static int fpreg_post_load(void *opaque, int version)
    175{
    176    x86_FPReg_tmp *tmp = opaque;
    177
    178    tmp->parent->d = cpu_set_fp80(tmp->tmp_mant, tmp->tmp_exp);
    179    return 0;
    180}
    181
    182static const VMStateDescription vmstate_fpreg_tmp = {
    183    .name = "fpreg_tmp",
    184    .post_load = fpreg_post_load,
    185    .pre_save  = fpreg_pre_save,
    186    .fields = (VMStateField[]) {
    187        VMSTATE_UINT64(tmp_mant, x86_FPReg_tmp),
    188        VMSTATE_UINT16(tmp_exp, x86_FPReg_tmp),
    189        VMSTATE_END_OF_LIST()
    190    }
    191};
    192
    193static const VMStateDescription vmstate_fpreg = {
    194    .name = "fpreg",
    195    .fields = (VMStateField[]) {
    196        VMSTATE_WITH_TMP(FPReg, x86_FPReg_tmp, vmstate_fpreg_tmp),
    197        VMSTATE_END_OF_LIST()
    198    }
    199};
    200
    201static int cpu_pre_save(void *opaque)
    202{
    203    X86CPU *cpu = opaque;
    204    CPUX86State *env = &cpu->env;
    205    int i;
    206    env->v_tpr = env->int_ctl & V_TPR_MASK;
    207    /* FPU */
    208    env->fpus_vmstate = (env->fpus & ~0x3800) | (env->fpstt & 0x7) << 11;
    209    env->fptag_vmstate = 0;
    210    for(i = 0; i < 8; i++) {
    211        env->fptag_vmstate |= ((!env->fptags[i]) << i);
    212    }
    213
    214    env->fpregs_format_vmstate = 0;
    215
    216    /*
    217     * Real mode guest segments register DPL should be zero.
    218     * Older KVM version were setting it wrongly.
    219     * Fixing it will allow live migration to host with unrestricted guest
    220     * support (otherwise the migration will fail with invalid guest state
    221     * error).
    222     */
    223    if (!(env->cr[0] & CR0_PE_MASK) &&
    224        (env->segs[R_CS].flags >> DESC_DPL_SHIFT & 3) != 0) {
    225        env->segs[R_CS].flags &= ~(env->segs[R_CS].flags & DESC_DPL_MASK);
    226        env->segs[R_DS].flags &= ~(env->segs[R_DS].flags & DESC_DPL_MASK);
    227        env->segs[R_ES].flags &= ~(env->segs[R_ES].flags & DESC_DPL_MASK);
    228        env->segs[R_FS].flags &= ~(env->segs[R_FS].flags & DESC_DPL_MASK);
    229        env->segs[R_GS].flags &= ~(env->segs[R_GS].flags & DESC_DPL_MASK);
    230        env->segs[R_SS].flags &= ~(env->segs[R_SS].flags & DESC_DPL_MASK);
    231    }
    232
    233#ifdef CONFIG_KVM
    234    /*
    235     * In case vCPU may have enabled VMX, we need to make sure kernel have
    236     * required capabilities in order to perform migration correctly:
    237     *
    238     * 1) We must be able to extract vCPU nested-state from KVM.
    239     *
    240     * 2) In case vCPU is running in guest-mode and it has a pending exception,
    241     * we must be able to determine if it's in a pending or injected state.
    242     * Note that in case KVM don't have required capability to do so,
    243     * a pending/injected exception will always appear as an
    244     * injected exception.
    245     */
    246    if (kvm_enabled() && cpu_vmx_maybe_enabled(env) &&
    247        (!env->nested_state ||
    248         (!kvm_has_exception_payload() && (env->hflags & HF_GUEST_MASK) &&
    249          env->exception_injected))) {
    250        error_report("Guest maybe enabled nested virtualization but kernel "
    251                "does not support required capabilities to save vCPU "
    252                "nested state");
    253        return -EINVAL;
    254    }
    255#endif
    256
    257    /*
    258     * When vCPU is running L2 and exception is still pending,
    259     * it can potentially be intercepted by L1 hypervisor.
    260     * In contrast to an injected exception which cannot be
    261     * intercepted anymore.
    262     *
    263     * Furthermore, when a L2 exception is intercepted by L1
    264     * hypervisor, its exception payload (CR2/DR6 on #PF/#DB)
    265     * should not be set yet in the respective vCPU register.
    266     * Thus, in case an exception is pending, it is
    267     * important to save the exception payload seperately.
    268     *
    269     * Therefore, if an exception is not in a pending state
    270     * or vCPU is not in guest-mode, it is not important to
    271     * distinguish between a pending and injected exception
    272     * and we don't need to store seperately the exception payload.
    273     *
    274     * In order to preserve better backwards-compatible migration,
    275     * convert a pending exception to an injected exception in
    276     * case it is not important to distinguish between them
    277     * as described above.
    278     */
    279    if (env->exception_pending && !(env->hflags & HF_GUEST_MASK)) {
    280        env->exception_pending = 0;
    281        env->exception_injected = 1;
    282
    283        if (env->exception_has_payload) {
    284            if (env->exception_nr == EXCP01_DB) {
    285                env->dr[6] = env->exception_payload;
    286            } else if (env->exception_nr == EXCP0E_PAGE) {
    287                env->cr[2] = env->exception_payload;
    288            }
    289        }
    290    }
    291
    292    return 0;
    293}
    294
    295static int cpu_post_load(void *opaque, int version_id)
    296{
    297    X86CPU *cpu = opaque;
    298    CPUState *cs = CPU(cpu);
    299    CPUX86State *env = &cpu->env;
    300    int i;
    301
    302    if (env->tsc_khz && env->user_tsc_khz &&
    303        env->tsc_khz != env->user_tsc_khz) {
    304        error_report("Mismatch between user-specified TSC frequency and "
    305                     "migrated TSC frequency");
    306        return -EINVAL;
    307    }
    308
    309    if (env->fpregs_format_vmstate) {
    310        error_report("Unsupported old non-softfloat CPU state");
    311        return -EINVAL;
    312    }
    313    /*
    314     * Real mode guest segments register DPL should be zero.
    315     * Older KVM version were setting it wrongly.
    316     * Fixing it will allow live migration from such host that don't have
    317     * restricted guest support to a host with unrestricted guest support
    318     * (otherwise the migration will fail with invalid guest state
    319     * error).
    320     */
    321    if (!(env->cr[0] & CR0_PE_MASK) &&
    322        (env->segs[R_CS].flags >> DESC_DPL_SHIFT & 3) != 0) {
    323        env->segs[R_CS].flags &= ~(env->segs[R_CS].flags & DESC_DPL_MASK);
    324        env->segs[R_DS].flags &= ~(env->segs[R_DS].flags & DESC_DPL_MASK);
    325        env->segs[R_ES].flags &= ~(env->segs[R_ES].flags & DESC_DPL_MASK);
    326        env->segs[R_FS].flags &= ~(env->segs[R_FS].flags & DESC_DPL_MASK);
    327        env->segs[R_GS].flags &= ~(env->segs[R_GS].flags & DESC_DPL_MASK);
    328        env->segs[R_SS].flags &= ~(env->segs[R_SS].flags & DESC_DPL_MASK);
    329    }
    330
    331    /* Older versions of QEMU incorrectly used CS.DPL as the CPL when
    332     * running under KVM.  This is wrong for conforming code segments.
    333     * Luckily, in our implementation the CPL field of hflags is redundant
    334     * and we can get the right value from the SS descriptor privilege level.
    335     */
    336    env->hflags &= ~HF_CPL_MASK;
    337    env->hflags |= (env->segs[R_SS].flags >> DESC_DPL_SHIFT) & HF_CPL_MASK;
    338
    339#ifdef CONFIG_KVM
    340    if ((env->hflags & HF_GUEST_MASK) &&
    341        (!env->nested_state ||
    342        !(env->nested_state->flags & KVM_STATE_NESTED_GUEST_MODE))) {
    343        error_report("vCPU set in guest-mode inconsistent with "
    344                     "migrated kernel nested state");
    345        return -EINVAL;
    346    }
    347#endif
    348
    349    /*
    350     * There are cases that we can get valid exception_nr with both
    351     * exception_pending and exception_injected being cleared.
    352     * This can happen in one of the following scenarios:
    353     * 1) Source is older QEMU without KVM_CAP_EXCEPTION_PAYLOAD support.
    354     * 2) Source is running on kernel without KVM_CAP_EXCEPTION_PAYLOAD support.
    355     * 3) "cpu/exception_info" subsection not sent because there is no exception
    356     *    pending or guest wasn't running L2 (See comment in cpu_pre_save()).
    357     *
    358     * In those cases, we can just deduce that a valid exception_nr means
    359     * we can treat the exception as already injected.
    360     */
    361    if ((env->exception_nr != -1) &&
    362        !env->exception_pending && !env->exception_injected) {
    363        env->exception_injected = 1;
    364    }
    365
    366    env->fpstt = (env->fpus_vmstate >> 11) & 7;
    367    env->fpus = env->fpus_vmstate & ~0x3800;
    368    env->fptag_vmstate ^= 0xff;
    369    for(i = 0; i < 8; i++) {
    370        env->fptags[i] = (env->fptag_vmstate >> i) & 1;
    371    }
    372    if (tcg_enabled()) {
    373        target_ulong dr7;
    374        update_fp_status(env);
    375        update_mxcsr_status(env);
    376
    377        cpu_breakpoint_remove_all(cs, BP_CPU);
    378        cpu_watchpoint_remove_all(cs, BP_CPU);
    379
    380        /* Indicate all breakpoints disabled, as they are, then
    381           let the helper re-enable them.  */
    382        dr7 = env->dr[7];
    383        env->dr[7] = dr7 & ~(DR7_GLOBAL_BP_MASK | DR7_LOCAL_BP_MASK);
    384        cpu_x86_update_dr7(env, dr7);
    385    }
    386    tlb_flush(cs);
    387    return 0;
    388}
    389
    390static bool async_pf_msr_needed(void *opaque)
    391{
    392    X86CPU *cpu = opaque;
    393
    394    return cpu->env.async_pf_en_msr != 0;
    395}
    396
    397static bool async_pf_int_msr_needed(void *opaque)
    398{
    399    X86CPU *cpu = opaque;
    400
    401    return cpu->env.async_pf_int_msr != 0;
    402}
    403
    404static bool pv_eoi_msr_needed(void *opaque)
    405{
    406    X86CPU *cpu = opaque;
    407
    408    return cpu->env.pv_eoi_en_msr != 0;
    409}
    410
    411static bool steal_time_msr_needed(void *opaque)
    412{
    413    X86CPU *cpu = opaque;
    414
    415    return cpu->env.steal_time_msr != 0;
    416}
    417
    418static bool exception_info_needed(void *opaque)
    419{
    420    X86CPU *cpu = opaque;
    421    CPUX86State *env = &cpu->env;
    422
    423    /*
    424     * It is important to save exception-info only in case
    425     * we need to distinguish between a pending and injected
    426     * exception. Which is only required in case there is a
    427     * pending exception and vCPU is running L2.
    428     * For more info, refer to comment in cpu_pre_save().
    429     */
    430    return env->exception_pending && (env->hflags & HF_GUEST_MASK);
    431}
    432
    433static const VMStateDescription vmstate_exception_info = {
    434    .name = "cpu/exception_info",
    435    .version_id = 1,
    436    .minimum_version_id = 1,
    437    .needed = exception_info_needed,
    438    .fields = (VMStateField[]) {
    439        VMSTATE_UINT8(env.exception_pending, X86CPU),
    440        VMSTATE_UINT8(env.exception_injected, X86CPU),
    441        VMSTATE_UINT8(env.exception_has_payload, X86CPU),
    442        VMSTATE_UINT64(env.exception_payload, X86CPU),
    443        VMSTATE_END_OF_LIST()
    444    }
    445};
    446
    447/* Poll control MSR enabled by default */
    448static bool poll_control_msr_needed(void *opaque)
    449{
    450    X86CPU *cpu = opaque;
    451
    452    return cpu->env.poll_control_msr != 1;
    453}
    454
    455static const VMStateDescription vmstate_steal_time_msr = {
    456    .name = "cpu/steal_time_msr",
    457    .version_id = 1,
    458    .minimum_version_id = 1,
    459    .needed = steal_time_msr_needed,
    460    .fields = (VMStateField[]) {
    461        VMSTATE_UINT64(env.steal_time_msr, X86CPU),
    462        VMSTATE_END_OF_LIST()
    463    }
    464};
    465
    466static const VMStateDescription vmstate_async_pf_msr = {
    467    .name = "cpu/async_pf_msr",
    468    .version_id = 1,
    469    .minimum_version_id = 1,
    470    .needed = async_pf_msr_needed,
    471    .fields = (VMStateField[]) {
    472        VMSTATE_UINT64(env.async_pf_en_msr, X86CPU),
    473        VMSTATE_END_OF_LIST()
    474    }
    475};
    476
    477static const VMStateDescription vmstate_async_pf_int_msr = {
    478    .name = "cpu/async_pf_int_msr",
    479    .version_id = 1,
    480    .minimum_version_id = 1,
    481    .needed = async_pf_int_msr_needed,
    482    .fields = (VMStateField[]) {
    483        VMSTATE_UINT64(env.async_pf_int_msr, X86CPU),
    484        VMSTATE_END_OF_LIST()
    485    }
    486};
    487
    488static const VMStateDescription vmstate_pv_eoi_msr = {
    489    .name = "cpu/async_pv_eoi_msr",
    490    .version_id = 1,
    491    .minimum_version_id = 1,
    492    .needed = pv_eoi_msr_needed,
    493    .fields = (VMStateField[]) {
    494        VMSTATE_UINT64(env.pv_eoi_en_msr, X86CPU),
    495        VMSTATE_END_OF_LIST()
    496    }
    497};
    498
    499static const VMStateDescription vmstate_poll_control_msr = {
    500    .name = "cpu/poll_control_msr",
    501    .version_id = 1,
    502    .minimum_version_id = 1,
    503    .needed = poll_control_msr_needed,
    504    .fields = (VMStateField[]) {
    505        VMSTATE_UINT64(env.poll_control_msr, X86CPU),
    506        VMSTATE_END_OF_LIST()
    507    }
    508};
    509
    510static bool fpop_ip_dp_needed(void *opaque)
    511{
    512    X86CPU *cpu = opaque;
    513    CPUX86State *env = &cpu->env;
    514
    515    return env->fpop != 0 || env->fpip != 0 || env->fpdp != 0;
    516}
    517
    518static const VMStateDescription vmstate_fpop_ip_dp = {
    519    .name = "cpu/fpop_ip_dp",
    520    .version_id = 1,
    521    .minimum_version_id = 1,
    522    .needed = fpop_ip_dp_needed,
    523    .fields = (VMStateField[]) {
    524        VMSTATE_UINT16(env.fpop, X86CPU),
    525        VMSTATE_UINT64(env.fpip, X86CPU),
    526        VMSTATE_UINT64(env.fpdp, X86CPU),
    527        VMSTATE_END_OF_LIST()
    528    }
    529};
    530
    531static bool tsc_adjust_needed(void *opaque)
    532{
    533    X86CPU *cpu = opaque;
    534    CPUX86State *env = &cpu->env;
    535
    536    return env->tsc_adjust != 0;
    537}
    538
    539static const VMStateDescription vmstate_msr_tsc_adjust = {
    540    .name = "cpu/msr_tsc_adjust",
    541    .version_id = 1,
    542    .minimum_version_id = 1,
    543    .needed = tsc_adjust_needed,
    544    .fields = (VMStateField[]) {
    545        VMSTATE_UINT64(env.tsc_adjust, X86CPU),
    546        VMSTATE_END_OF_LIST()
    547    }
    548};
    549
    550static bool msr_smi_count_needed(void *opaque)
    551{
    552    X86CPU *cpu = opaque;
    553    CPUX86State *env = &cpu->env;
    554
    555    return cpu->migrate_smi_count && env->msr_smi_count != 0;
    556}
    557
    558static const VMStateDescription vmstate_msr_smi_count = {
    559    .name = "cpu/msr_smi_count",
    560    .version_id = 1,
    561    .minimum_version_id = 1,
    562    .needed = msr_smi_count_needed,
    563    .fields = (VMStateField[]) {
    564        VMSTATE_UINT64(env.msr_smi_count, X86CPU),
    565        VMSTATE_END_OF_LIST()
    566    }
    567};
    568
    569static bool tscdeadline_needed(void *opaque)
    570{
    571    X86CPU *cpu = opaque;
    572    CPUX86State *env = &cpu->env;
    573
    574    return env->tsc_deadline != 0;
    575}
    576
    577static const VMStateDescription vmstate_msr_tscdeadline = {
    578    .name = "cpu/msr_tscdeadline",
    579    .version_id = 1,
    580    .minimum_version_id = 1,
    581    .needed = tscdeadline_needed,
    582    .fields = (VMStateField[]) {
    583        VMSTATE_UINT64(env.tsc_deadline, X86CPU),
    584        VMSTATE_END_OF_LIST()
    585    }
    586};
    587
    588static bool misc_enable_needed(void *opaque)
    589{
    590    X86CPU *cpu = opaque;
    591    CPUX86State *env = &cpu->env;
    592
    593    return env->msr_ia32_misc_enable != MSR_IA32_MISC_ENABLE_DEFAULT;
    594}
    595
    596static bool feature_control_needed(void *opaque)
    597{
    598    X86CPU *cpu = opaque;
    599    CPUX86State *env = &cpu->env;
    600
    601    return env->msr_ia32_feature_control != 0;
    602}
    603
    604static const VMStateDescription vmstate_msr_ia32_misc_enable = {
    605    .name = "cpu/msr_ia32_misc_enable",
    606    .version_id = 1,
    607    .minimum_version_id = 1,
    608    .needed = misc_enable_needed,
    609    .fields = (VMStateField[]) {
    610        VMSTATE_UINT64(env.msr_ia32_misc_enable, X86CPU),
    611        VMSTATE_END_OF_LIST()
    612    }
    613};
    614
    615static const VMStateDescription vmstate_msr_ia32_feature_control = {
    616    .name = "cpu/msr_ia32_feature_control",
    617    .version_id = 1,
    618    .minimum_version_id = 1,
    619    .needed = feature_control_needed,
    620    .fields = (VMStateField[]) {
    621        VMSTATE_UINT64(env.msr_ia32_feature_control, X86CPU),
    622        VMSTATE_END_OF_LIST()
    623    }
    624};
    625
    626static bool pmu_enable_needed(void *opaque)
    627{
    628    X86CPU *cpu = opaque;
    629    CPUX86State *env = &cpu->env;
    630    int i;
    631
    632    if (env->msr_fixed_ctr_ctrl || env->msr_global_ctrl ||
    633        env->msr_global_status || env->msr_global_ovf_ctrl) {
    634        return true;
    635    }
    636    for (i = 0; i < MAX_FIXED_COUNTERS; i++) {
    637        if (env->msr_fixed_counters[i]) {
    638            return true;
    639        }
    640    }
    641    for (i = 0; i < MAX_GP_COUNTERS; i++) {
    642        if (env->msr_gp_counters[i] || env->msr_gp_evtsel[i]) {
    643            return true;
    644        }
    645    }
    646
    647    return false;
    648}
    649
    650static const VMStateDescription vmstate_msr_architectural_pmu = {
    651    .name = "cpu/msr_architectural_pmu",
    652    .version_id = 1,
    653    .minimum_version_id = 1,
    654    .needed = pmu_enable_needed,
    655    .fields = (VMStateField[]) {
    656        VMSTATE_UINT64(env.msr_fixed_ctr_ctrl, X86CPU),
    657        VMSTATE_UINT64(env.msr_global_ctrl, X86CPU),
    658        VMSTATE_UINT64(env.msr_global_status, X86CPU),
    659        VMSTATE_UINT64(env.msr_global_ovf_ctrl, X86CPU),
    660        VMSTATE_UINT64_ARRAY(env.msr_fixed_counters, X86CPU, MAX_FIXED_COUNTERS),
    661        VMSTATE_UINT64_ARRAY(env.msr_gp_counters, X86CPU, MAX_GP_COUNTERS),
    662        VMSTATE_UINT64_ARRAY(env.msr_gp_evtsel, X86CPU, MAX_GP_COUNTERS),
    663        VMSTATE_END_OF_LIST()
    664    }
    665};
    666
    667static bool mpx_needed(void *opaque)
    668{
    669    X86CPU *cpu = opaque;
    670    CPUX86State *env = &cpu->env;
    671    unsigned int i;
    672
    673    for (i = 0; i < 4; i++) {
    674        if (env->bnd_regs[i].lb || env->bnd_regs[i].ub) {
    675            return true;
    676        }
    677    }
    678
    679    if (env->bndcs_regs.cfgu || env->bndcs_regs.sts) {
    680        return true;
    681    }
    682
    683    return !!env->msr_bndcfgs;
    684}
    685
    686static const VMStateDescription vmstate_mpx = {
    687    .name = "cpu/mpx",
    688    .version_id = 1,
    689    .minimum_version_id = 1,
    690    .needed = mpx_needed,
    691    .fields = (VMStateField[]) {
    692        VMSTATE_BND_REGS(env.bnd_regs, X86CPU, 4),
    693        VMSTATE_UINT64(env.bndcs_regs.cfgu, X86CPU),
    694        VMSTATE_UINT64(env.bndcs_regs.sts, X86CPU),
    695        VMSTATE_UINT64(env.msr_bndcfgs, X86CPU),
    696        VMSTATE_END_OF_LIST()
    697    }
    698};
    699
    700static bool hyperv_hypercall_enable_needed(void *opaque)
    701{
    702    X86CPU *cpu = opaque;
    703    CPUX86State *env = &cpu->env;
    704
    705    return env->msr_hv_hypercall != 0 || env->msr_hv_guest_os_id != 0;
    706}
    707
    708static const VMStateDescription vmstate_msr_hyperv_hypercall = {
    709    .name = "cpu/msr_hyperv_hypercall",
    710    .version_id = 1,
    711    .minimum_version_id = 1,
    712    .needed = hyperv_hypercall_enable_needed,
    713    .fields = (VMStateField[]) {
    714        VMSTATE_UINT64(env.msr_hv_guest_os_id, X86CPU),
    715        VMSTATE_UINT64(env.msr_hv_hypercall, X86CPU),
    716        VMSTATE_END_OF_LIST()
    717    }
    718};
    719
    720static bool hyperv_vapic_enable_needed(void *opaque)
    721{
    722    X86CPU *cpu = opaque;
    723    CPUX86State *env = &cpu->env;
    724
    725    return env->msr_hv_vapic != 0;
    726}
    727
    728static const VMStateDescription vmstate_msr_hyperv_vapic = {
    729    .name = "cpu/msr_hyperv_vapic",
    730    .version_id = 1,
    731    .minimum_version_id = 1,
    732    .needed = hyperv_vapic_enable_needed,
    733    .fields = (VMStateField[]) {
    734        VMSTATE_UINT64(env.msr_hv_vapic, X86CPU),
    735        VMSTATE_END_OF_LIST()
    736    }
    737};
    738
    739static bool hyperv_time_enable_needed(void *opaque)
    740{
    741    X86CPU *cpu = opaque;
    742    CPUX86State *env = &cpu->env;
    743
    744    return env->msr_hv_tsc != 0;
    745}
    746
    747static const VMStateDescription vmstate_msr_hyperv_time = {
    748    .name = "cpu/msr_hyperv_time",
    749    .version_id = 1,
    750    .minimum_version_id = 1,
    751    .needed = hyperv_time_enable_needed,
    752    .fields = (VMStateField[]) {
    753        VMSTATE_UINT64(env.msr_hv_tsc, X86CPU),
    754        VMSTATE_END_OF_LIST()
    755    }
    756};
    757
    758static bool hyperv_crash_enable_needed(void *opaque)
    759{
    760    X86CPU *cpu = opaque;
    761    CPUX86State *env = &cpu->env;
    762    int i;
    763
    764    for (i = 0; i < HV_CRASH_PARAMS; i++) {
    765        if (env->msr_hv_crash_params[i]) {
    766            return true;
    767        }
    768    }
    769    return false;
    770}
    771
    772static const VMStateDescription vmstate_msr_hyperv_crash = {
    773    .name = "cpu/msr_hyperv_crash",
    774    .version_id = 1,
    775    .minimum_version_id = 1,
    776    .needed = hyperv_crash_enable_needed,
    777    .fields = (VMStateField[]) {
    778        VMSTATE_UINT64_ARRAY(env.msr_hv_crash_params, X86CPU, HV_CRASH_PARAMS),
    779        VMSTATE_END_OF_LIST()
    780    }
    781};
    782
    783static bool hyperv_runtime_enable_needed(void *opaque)
    784{
    785    X86CPU *cpu = opaque;
    786    CPUX86State *env = &cpu->env;
    787
    788    if (!hyperv_feat_enabled(cpu, HYPERV_FEAT_RUNTIME)) {
    789        return false;
    790    }
    791
    792    return env->msr_hv_runtime != 0;
    793}
    794
    795static const VMStateDescription vmstate_msr_hyperv_runtime = {
    796    .name = "cpu/msr_hyperv_runtime",
    797    .version_id = 1,
    798    .minimum_version_id = 1,
    799    .needed = hyperv_runtime_enable_needed,
    800    .fields = (VMStateField[]) {
    801        VMSTATE_UINT64(env.msr_hv_runtime, X86CPU),
    802        VMSTATE_END_OF_LIST()
    803    }
    804};
    805
    806static bool hyperv_synic_enable_needed(void *opaque)
    807{
    808    X86CPU *cpu = opaque;
    809    CPUX86State *env = &cpu->env;
    810    int i;
    811
    812    if (env->msr_hv_synic_control != 0 ||
    813        env->msr_hv_synic_evt_page != 0 ||
    814        env->msr_hv_synic_msg_page != 0) {
    815        return true;
    816    }
    817
    818    for (i = 0; i < ARRAY_SIZE(env->msr_hv_synic_sint); i++) {
    819        if (env->msr_hv_synic_sint[i] != 0) {
    820            return true;
    821        }
    822    }
    823
    824    return false;
    825}
    826
    827static int hyperv_synic_post_load(void *opaque, int version_id)
    828{
    829    X86CPU *cpu = opaque;
    830    hyperv_x86_synic_update(cpu);
    831    return 0;
    832}
    833
    834static const VMStateDescription vmstate_msr_hyperv_synic = {
    835    .name = "cpu/msr_hyperv_synic",
    836    .version_id = 1,
    837    .minimum_version_id = 1,
    838    .needed = hyperv_synic_enable_needed,
    839    .post_load = hyperv_synic_post_load,
    840    .fields = (VMStateField[]) {
    841        VMSTATE_UINT64(env.msr_hv_synic_control, X86CPU),
    842        VMSTATE_UINT64(env.msr_hv_synic_evt_page, X86CPU),
    843        VMSTATE_UINT64(env.msr_hv_synic_msg_page, X86CPU),
    844        VMSTATE_UINT64_ARRAY(env.msr_hv_synic_sint, X86CPU, HV_SINT_COUNT),
    845        VMSTATE_END_OF_LIST()
    846    }
    847};
    848
    849static bool hyperv_stimer_enable_needed(void *opaque)
    850{
    851    X86CPU *cpu = opaque;
    852    CPUX86State *env = &cpu->env;
    853    int i;
    854
    855    for (i = 0; i < ARRAY_SIZE(env->msr_hv_stimer_config); i++) {
    856        if (env->msr_hv_stimer_config[i] || env->msr_hv_stimer_count[i]) {
    857            return true;
    858        }
    859    }
    860    return false;
    861}
    862
    863static const VMStateDescription vmstate_msr_hyperv_stimer = {
    864    .name = "cpu/msr_hyperv_stimer",
    865    .version_id = 1,
    866    .minimum_version_id = 1,
    867    .needed = hyperv_stimer_enable_needed,
    868    .fields = (VMStateField[]) {
    869        VMSTATE_UINT64_ARRAY(env.msr_hv_stimer_config, X86CPU,
    870                             HV_STIMER_COUNT),
    871        VMSTATE_UINT64_ARRAY(env.msr_hv_stimer_count, X86CPU, HV_STIMER_COUNT),
    872        VMSTATE_END_OF_LIST()
    873    }
    874};
    875
    876static bool hyperv_reenlightenment_enable_needed(void *opaque)
    877{
    878    X86CPU *cpu = opaque;
    879    CPUX86State *env = &cpu->env;
    880
    881    return env->msr_hv_reenlightenment_control != 0 ||
    882        env->msr_hv_tsc_emulation_control != 0 ||
    883        env->msr_hv_tsc_emulation_status != 0;
    884}
    885
    886static int hyperv_reenlightenment_post_load(void *opaque, int version_id)
    887{
    888    X86CPU *cpu = opaque;
    889    CPUX86State *env = &cpu->env;
    890
    891    /*
    892     * KVM doesn't fully support re-enlightenment notifications so we need to
    893     * make sure TSC frequency doesn't change upon migration.
    894     */
    895    if ((env->msr_hv_reenlightenment_control & HV_REENLIGHTENMENT_ENABLE_BIT) &&
    896        !env->user_tsc_khz) {
    897        error_report("Guest enabled re-enlightenment notifications, "
    898                     "'tsc-frequency=' has to be specified");
    899        return -EINVAL;
    900    }
    901
    902    return 0;
    903}
    904
    905static const VMStateDescription vmstate_msr_hyperv_reenlightenment = {
    906    .name = "cpu/msr_hyperv_reenlightenment",
    907    .version_id = 1,
    908    .minimum_version_id = 1,
    909    .needed = hyperv_reenlightenment_enable_needed,
    910    .post_load = hyperv_reenlightenment_post_load,
    911    .fields = (VMStateField[]) {
    912        VMSTATE_UINT64(env.msr_hv_reenlightenment_control, X86CPU),
    913        VMSTATE_UINT64(env.msr_hv_tsc_emulation_control, X86CPU),
    914        VMSTATE_UINT64(env.msr_hv_tsc_emulation_status, X86CPU),
    915        VMSTATE_END_OF_LIST()
    916    }
    917};
    918
    919static bool avx512_needed(void *opaque)
    920{
    921    X86CPU *cpu = opaque;
    922    CPUX86State *env = &cpu->env;
    923    unsigned int i;
    924
    925    for (i = 0; i < NB_OPMASK_REGS; i++) {
    926        if (env->opmask_regs[i]) {
    927            return true;
    928        }
    929    }
    930
    931    for (i = 0; i < CPU_NB_REGS; i++) {
    932#define ENV_XMM(reg, field) (env->xmm_regs[reg].ZMM_Q(field))
    933        if (ENV_XMM(i, 4) || ENV_XMM(i, 6) ||
    934            ENV_XMM(i, 5) || ENV_XMM(i, 7)) {
    935            return true;
    936        }
    937#ifdef TARGET_X86_64
    938        if (ENV_XMM(i+16, 0) || ENV_XMM(i+16, 1) ||
    939            ENV_XMM(i+16, 2) || ENV_XMM(i+16, 3) ||
    940            ENV_XMM(i+16, 4) || ENV_XMM(i+16, 5) ||
    941            ENV_XMM(i+16, 6) || ENV_XMM(i+16, 7)) {
    942            return true;
    943        }
    944#endif
    945    }
    946
    947    return false;
    948}
    949
    950static const VMStateDescription vmstate_avx512 = {
    951    .name = "cpu/avx512",
    952    .version_id = 1,
    953    .minimum_version_id = 1,
    954    .needed = avx512_needed,
    955    .fields = (VMStateField[]) {
    956        VMSTATE_UINT64_ARRAY(env.opmask_regs, X86CPU, NB_OPMASK_REGS),
    957        VMSTATE_ZMMH_REGS_VARS(env.xmm_regs, X86CPU, 0),
    958#ifdef TARGET_X86_64
    959        VMSTATE_Hi16_ZMM_REGS_VARS(env.xmm_regs, X86CPU, 16),
    960#endif
    961        VMSTATE_END_OF_LIST()
    962    }
    963};
    964
    965static bool xss_needed(void *opaque)
    966{
    967    X86CPU *cpu = opaque;
    968    CPUX86State *env = &cpu->env;
    969
    970    return env->xss != 0;
    971}
    972
    973static const VMStateDescription vmstate_xss = {
    974    .name = "cpu/xss",
    975    .version_id = 1,
    976    .minimum_version_id = 1,
    977    .needed = xss_needed,
    978    .fields = (VMStateField[]) {
    979        VMSTATE_UINT64(env.xss, X86CPU),
    980        VMSTATE_END_OF_LIST()
    981    }
    982};
    983
    984static bool umwait_needed(void *opaque)
    985{
    986    X86CPU *cpu = opaque;
    987    CPUX86State *env = &cpu->env;
    988
    989    return env->umwait != 0;
    990}
    991
    992static const VMStateDescription vmstate_umwait = {
    993    .name = "cpu/umwait",
    994    .version_id = 1,
    995    .minimum_version_id = 1,
    996    .needed = umwait_needed,
    997    .fields = (VMStateField[]) {
    998        VMSTATE_UINT32(env.umwait, X86CPU),
    999        VMSTATE_END_OF_LIST()
   1000    }
   1001};
   1002
   1003static bool pkru_needed(void *opaque)
   1004{
   1005    X86CPU *cpu = opaque;
   1006    CPUX86State *env = &cpu->env;
   1007
   1008    return env->pkru != 0;
   1009}
   1010
   1011static const VMStateDescription vmstate_pkru = {
   1012    .name = "cpu/pkru",
   1013    .version_id = 1,
   1014    .minimum_version_id = 1,
   1015    .needed = pkru_needed,
   1016    .fields = (VMStateField[]){
   1017        VMSTATE_UINT32(env.pkru, X86CPU),
   1018        VMSTATE_END_OF_LIST()
   1019    }
   1020};
   1021
   1022static bool pkrs_needed(void *opaque)
   1023{
   1024    X86CPU *cpu = opaque;
   1025    CPUX86State *env = &cpu->env;
   1026
   1027    return env->pkrs != 0;
   1028}
   1029
   1030static const VMStateDescription vmstate_pkrs = {
   1031    .name = "cpu/pkrs",
   1032    .version_id = 1,
   1033    .minimum_version_id = 1,
   1034    .needed = pkrs_needed,
   1035    .fields = (VMStateField[]){
   1036        VMSTATE_UINT32(env.pkrs, X86CPU),
   1037        VMSTATE_END_OF_LIST()
   1038    }
   1039};
   1040
   1041static bool tsc_khz_needed(void *opaque)
   1042{
   1043    X86CPU *cpu = opaque;
   1044    CPUX86State *env = &cpu->env;
   1045    MachineClass *mc = MACHINE_GET_CLASS(qdev_get_machine());
   1046    X86MachineClass *x86mc = X86_MACHINE_CLASS(mc);
   1047    return env->tsc_khz && x86mc->save_tsc_khz;
   1048}
   1049
   1050static const VMStateDescription vmstate_tsc_khz = {
   1051    .name = "cpu/tsc_khz",
   1052    .version_id = 1,
   1053    .minimum_version_id = 1,
   1054    .needed = tsc_khz_needed,
   1055    .fields = (VMStateField[]) {
   1056        VMSTATE_INT64(env.tsc_khz, X86CPU),
   1057        VMSTATE_END_OF_LIST()
   1058    }
   1059};
   1060
   1061#ifdef CONFIG_KVM
   1062
   1063static bool vmx_vmcs12_needed(void *opaque)
   1064{
   1065    struct kvm_nested_state *nested_state = opaque;
   1066    return (nested_state->size >
   1067            offsetof(struct kvm_nested_state, data.vmx[0].vmcs12));
   1068}
   1069
   1070static const VMStateDescription vmstate_vmx_vmcs12 = {
   1071    .name = "cpu/kvm_nested_state/vmx/vmcs12",
   1072    .version_id = 1,
   1073    .minimum_version_id = 1,
   1074    .needed = vmx_vmcs12_needed,
   1075    .fields = (VMStateField[]) {
   1076        VMSTATE_UINT8_ARRAY(data.vmx[0].vmcs12,
   1077                            struct kvm_nested_state,
   1078                            KVM_STATE_NESTED_VMX_VMCS_SIZE),
   1079        VMSTATE_END_OF_LIST()
   1080    }
   1081};
   1082
   1083static bool vmx_shadow_vmcs12_needed(void *opaque)
   1084{
   1085    struct kvm_nested_state *nested_state = opaque;
   1086    return (nested_state->size >
   1087            offsetof(struct kvm_nested_state, data.vmx[0].shadow_vmcs12));
   1088}
   1089
   1090static const VMStateDescription vmstate_vmx_shadow_vmcs12 = {
   1091    .name = "cpu/kvm_nested_state/vmx/shadow_vmcs12",
   1092    .version_id = 1,
   1093    .minimum_version_id = 1,
   1094    .needed = vmx_shadow_vmcs12_needed,
   1095    .fields = (VMStateField[]) {
   1096        VMSTATE_UINT8_ARRAY(data.vmx[0].shadow_vmcs12,
   1097                            struct kvm_nested_state,
   1098                            KVM_STATE_NESTED_VMX_VMCS_SIZE),
   1099        VMSTATE_END_OF_LIST()
   1100    }
   1101};
   1102
   1103static bool vmx_nested_state_needed(void *opaque)
   1104{
   1105    struct kvm_nested_state *nested_state = opaque;
   1106
   1107    return (nested_state->format == KVM_STATE_NESTED_FORMAT_VMX &&
   1108            nested_state->hdr.vmx.vmxon_pa != -1ull);
   1109}
   1110
   1111static const VMStateDescription vmstate_vmx_nested_state = {
   1112    .name = "cpu/kvm_nested_state/vmx",
   1113    .version_id = 1,
   1114    .minimum_version_id = 1,
   1115    .needed = vmx_nested_state_needed,
   1116    .fields = (VMStateField[]) {
   1117        VMSTATE_U64(hdr.vmx.vmxon_pa, struct kvm_nested_state),
   1118        VMSTATE_U64(hdr.vmx.vmcs12_pa, struct kvm_nested_state),
   1119        VMSTATE_U16(hdr.vmx.smm.flags, struct kvm_nested_state),
   1120        VMSTATE_END_OF_LIST()
   1121    },
   1122    .subsections = (const VMStateDescription*[]) {
   1123        &vmstate_vmx_vmcs12,
   1124        &vmstate_vmx_shadow_vmcs12,
   1125        NULL,
   1126    }
   1127};
   1128
   1129static bool svm_nested_state_needed(void *opaque)
   1130{
   1131    struct kvm_nested_state *nested_state = opaque;
   1132
   1133    /*
   1134     * HF_GUEST_MASK and HF2_GIF_MASK are already serialized
   1135     * via hflags and hflags2, all that's left is the opaque
   1136     * nested state blob.
   1137     */
   1138    return (nested_state->format == KVM_STATE_NESTED_FORMAT_SVM &&
   1139            nested_state->size > offsetof(struct kvm_nested_state, data));
   1140}
   1141
   1142static const VMStateDescription vmstate_svm_nested_state = {
   1143    .name = "cpu/kvm_nested_state/svm",
   1144    .version_id = 1,
   1145    .minimum_version_id = 1,
   1146    .needed = svm_nested_state_needed,
   1147    .fields = (VMStateField[]) {
   1148        VMSTATE_U64(hdr.svm.vmcb_pa, struct kvm_nested_state),
   1149        VMSTATE_UINT8_ARRAY(data.svm[0].vmcb12,
   1150                            struct kvm_nested_state,
   1151                            KVM_STATE_NESTED_SVM_VMCB_SIZE),
   1152        VMSTATE_END_OF_LIST()
   1153    }
   1154};
   1155
   1156static bool nested_state_needed(void *opaque)
   1157{
   1158    X86CPU *cpu = opaque;
   1159    CPUX86State *env = &cpu->env;
   1160
   1161    return (env->nested_state &&
   1162            (vmx_nested_state_needed(env->nested_state) ||
   1163             svm_nested_state_needed(env->nested_state)));
   1164}
   1165
   1166static int nested_state_post_load(void *opaque, int version_id)
   1167{
   1168    X86CPU *cpu = opaque;
   1169    CPUX86State *env = &cpu->env;
   1170    struct kvm_nested_state *nested_state = env->nested_state;
   1171    int min_nested_state_len = offsetof(struct kvm_nested_state, data);
   1172    int max_nested_state_len = kvm_max_nested_state_length();
   1173
   1174    /*
   1175     * If our kernel don't support setting nested state
   1176     * and we have received nested state from migration stream,
   1177     * we need to fail migration
   1178     */
   1179    if (max_nested_state_len <= 0) {
   1180        error_report("Received nested state when kernel cannot restore it");
   1181        return -EINVAL;
   1182    }
   1183
   1184    /*
   1185     * Verify that the size of received nested_state struct
   1186     * at least cover required header and is not larger
   1187     * than the max size that our kernel support
   1188     */
   1189    if (nested_state->size < min_nested_state_len) {
   1190        error_report("Received nested state size less than min: "
   1191                     "len=%d, min=%d",
   1192                     nested_state->size, min_nested_state_len);
   1193        return -EINVAL;
   1194    }
   1195    if (nested_state->size > max_nested_state_len) {
   1196        error_report("Received unsupported nested state size: "
   1197                     "nested_state->size=%d, max=%d",
   1198                     nested_state->size, max_nested_state_len);
   1199        return -EINVAL;
   1200    }
   1201
   1202    /* Verify format is valid */
   1203    if ((nested_state->format != KVM_STATE_NESTED_FORMAT_VMX) &&
   1204        (nested_state->format != KVM_STATE_NESTED_FORMAT_SVM)) {
   1205        error_report("Received invalid nested state format: %d",
   1206                     nested_state->format);
   1207        return -EINVAL;
   1208    }
   1209
   1210    return 0;
   1211}
   1212
   1213static const VMStateDescription vmstate_kvm_nested_state = {
   1214    .name = "cpu/kvm_nested_state",
   1215    .version_id = 1,
   1216    .minimum_version_id = 1,
   1217    .fields = (VMStateField[]) {
   1218        VMSTATE_U16(flags, struct kvm_nested_state),
   1219        VMSTATE_U16(format, struct kvm_nested_state),
   1220        VMSTATE_U32(size, struct kvm_nested_state),
   1221        VMSTATE_END_OF_LIST()
   1222    },
   1223    .subsections = (const VMStateDescription*[]) {
   1224        &vmstate_vmx_nested_state,
   1225        &vmstate_svm_nested_state,
   1226        NULL
   1227    }
   1228};
   1229
   1230static const VMStateDescription vmstate_nested_state = {
   1231    .name = "cpu/nested_state",
   1232    .version_id = 1,
   1233    .minimum_version_id = 1,
   1234    .needed = nested_state_needed,
   1235    .post_load = nested_state_post_load,
   1236    .fields = (VMStateField[]) {
   1237        VMSTATE_STRUCT_POINTER(env.nested_state, X86CPU,
   1238                vmstate_kvm_nested_state,
   1239                struct kvm_nested_state),
   1240        VMSTATE_END_OF_LIST()
   1241    }
   1242};
   1243
   1244#endif
   1245
   1246static bool mcg_ext_ctl_needed(void *opaque)
   1247{
   1248    X86CPU *cpu = opaque;
   1249    CPUX86State *env = &cpu->env;
   1250    return cpu->enable_lmce && env->mcg_ext_ctl;
   1251}
   1252
   1253static const VMStateDescription vmstate_mcg_ext_ctl = {
   1254    .name = "cpu/mcg_ext_ctl",
   1255    .version_id = 1,
   1256    .minimum_version_id = 1,
   1257    .needed = mcg_ext_ctl_needed,
   1258    .fields = (VMStateField[]) {
   1259        VMSTATE_UINT64(env.mcg_ext_ctl, X86CPU),
   1260        VMSTATE_END_OF_LIST()
   1261    }
   1262};
   1263
   1264static bool spec_ctrl_needed(void *opaque)
   1265{
   1266    X86CPU *cpu = opaque;
   1267    CPUX86State *env = &cpu->env;
   1268
   1269    return env->spec_ctrl != 0;
   1270}
   1271
   1272static const VMStateDescription vmstate_spec_ctrl = {
   1273    .name = "cpu/spec_ctrl",
   1274    .version_id = 1,
   1275    .minimum_version_id = 1,
   1276    .needed = spec_ctrl_needed,
   1277    .fields = (VMStateField[]){
   1278        VMSTATE_UINT64(env.spec_ctrl, X86CPU),
   1279        VMSTATE_END_OF_LIST()
   1280    }
   1281};
   1282
   1283static bool intel_pt_enable_needed(void *opaque)
   1284{
   1285    X86CPU *cpu = opaque;
   1286    CPUX86State *env = &cpu->env;
   1287    int i;
   1288
   1289    if (env->msr_rtit_ctrl || env->msr_rtit_status ||
   1290        env->msr_rtit_output_base || env->msr_rtit_output_mask ||
   1291        env->msr_rtit_cr3_match) {
   1292        return true;
   1293    }
   1294
   1295    for (i = 0; i < MAX_RTIT_ADDRS; i++) {
   1296        if (env->msr_rtit_addrs[i]) {
   1297            return true;
   1298        }
   1299    }
   1300
   1301    return false;
   1302}
   1303
   1304static const VMStateDescription vmstate_msr_intel_pt = {
   1305    .name = "cpu/intel_pt",
   1306    .version_id = 1,
   1307    .minimum_version_id = 1,
   1308    .needed = intel_pt_enable_needed,
   1309    .fields = (VMStateField[]) {
   1310        VMSTATE_UINT64(env.msr_rtit_ctrl, X86CPU),
   1311        VMSTATE_UINT64(env.msr_rtit_status, X86CPU),
   1312        VMSTATE_UINT64(env.msr_rtit_output_base, X86CPU),
   1313        VMSTATE_UINT64(env.msr_rtit_output_mask, X86CPU),
   1314        VMSTATE_UINT64(env.msr_rtit_cr3_match, X86CPU),
   1315        VMSTATE_UINT64_ARRAY(env.msr_rtit_addrs, X86CPU, MAX_RTIT_ADDRS),
   1316        VMSTATE_END_OF_LIST()
   1317    }
   1318};
   1319
   1320static bool virt_ssbd_needed(void *opaque)
   1321{
   1322    X86CPU *cpu = opaque;
   1323    CPUX86State *env = &cpu->env;
   1324
   1325    return env->virt_ssbd != 0;
   1326}
   1327
   1328static const VMStateDescription vmstate_msr_virt_ssbd = {
   1329    .name = "cpu/virt_ssbd",
   1330    .version_id = 1,
   1331    .minimum_version_id = 1,
   1332    .needed = virt_ssbd_needed,
   1333    .fields = (VMStateField[]){
   1334        VMSTATE_UINT64(env.virt_ssbd, X86CPU),
   1335        VMSTATE_END_OF_LIST()
   1336    }
   1337};
   1338
   1339static bool svm_npt_needed(void *opaque)
   1340{
   1341    X86CPU *cpu = opaque;
   1342    CPUX86State *env = &cpu->env;
   1343
   1344    return !!(env->hflags2 & HF2_NPT_MASK);
   1345}
   1346
   1347static const VMStateDescription vmstate_svm_npt = {
   1348    .name = "cpu/svn_npt",
   1349    .version_id = 1,
   1350    .minimum_version_id = 1,
   1351    .needed = svm_npt_needed,
   1352    .fields = (VMStateField[]){
   1353        VMSTATE_UINT64(env.nested_cr3, X86CPU),
   1354        VMSTATE_UINT32(env.nested_pg_mode, X86CPU),
   1355        VMSTATE_END_OF_LIST()
   1356    }
   1357};
   1358
   1359static bool svm_guest_needed(void *opaque)
   1360{
   1361    X86CPU *cpu = opaque;
   1362    CPUX86State *env = &cpu->env;
   1363
   1364    return tcg_enabled() && env->int_ctl;
   1365}
   1366
   1367static const VMStateDescription vmstate_svm_guest = {
   1368    .name = "cpu/svm_guest",
   1369    .version_id = 1,
   1370    .minimum_version_id = 1,
   1371    .needed = svm_guest_needed,
   1372    .fields = (VMStateField[]){
   1373        VMSTATE_UINT32(env.int_ctl, X86CPU),
   1374        VMSTATE_END_OF_LIST()
   1375    }
   1376};
   1377
   1378#ifndef TARGET_X86_64
   1379static bool intel_efer32_needed(void *opaque)
   1380{
   1381    X86CPU *cpu = opaque;
   1382    CPUX86State *env = &cpu->env;
   1383
   1384    return env->efer != 0;
   1385}
   1386
   1387static const VMStateDescription vmstate_efer32 = {
   1388    .name = "cpu/efer32",
   1389    .version_id = 1,
   1390    .minimum_version_id = 1,
   1391    .needed = intel_efer32_needed,
   1392    .fields = (VMStateField[]) {
   1393        VMSTATE_UINT64(env.efer, X86CPU),
   1394        VMSTATE_END_OF_LIST()
   1395    }
   1396};
   1397#endif
   1398
   1399static bool msr_tsx_ctrl_needed(void *opaque)
   1400{
   1401    X86CPU *cpu = opaque;
   1402    CPUX86State *env = &cpu->env;
   1403
   1404    return env->features[FEAT_ARCH_CAPABILITIES] & ARCH_CAP_TSX_CTRL_MSR;
   1405}
   1406
   1407static const VMStateDescription vmstate_msr_tsx_ctrl = {
   1408    .name = "cpu/msr_tsx_ctrl",
   1409    .version_id = 1,
   1410    .minimum_version_id = 1,
   1411    .needed = msr_tsx_ctrl_needed,
   1412    .fields = (VMStateField[]) {
   1413        VMSTATE_UINT32(env.tsx_ctrl, X86CPU),
   1414        VMSTATE_END_OF_LIST()
   1415    }
   1416};
   1417
   1418static bool intel_sgx_msrs_needed(void *opaque)
   1419{
   1420    X86CPU *cpu = opaque;
   1421    CPUX86State *env = &cpu->env;
   1422
   1423    return !!(env->features[FEAT_7_0_ECX] & CPUID_7_0_ECX_SGX_LC);
   1424}
   1425
   1426static const VMStateDescription vmstate_msr_intel_sgx = {
   1427    .name = "cpu/intel_sgx",
   1428    .version_id = 1,
   1429    .minimum_version_id = 1,
   1430    .needed = intel_sgx_msrs_needed,
   1431    .fields = (VMStateField[]) {
   1432        VMSTATE_UINT64_ARRAY(env.msr_ia32_sgxlepubkeyhash, X86CPU, 4),
   1433        VMSTATE_END_OF_LIST()
   1434    }
   1435};
   1436
   1437const VMStateDescription vmstate_x86_cpu = {
   1438    .name = "cpu",
   1439    .version_id = 12,
   1440    .minimum_version_id = 11,
   1441    .pre_save = cpu_pre_save,
   1442    .post_load = cpu_post_load,
   1443    .fields = (VMStateField[]) {
   1444        VMSTATE_UINTTL_ARRAY(env.regs, X86CPU, CPU_NB_REGS),
   1445        VMSTATE_UINTTL(env.eip, X86CPU),
   1446        VMSTATE_UINTTL(env.eflags, X86CPU),
   1447        VMSTATE_UINT32(env.hflags, X86CPU),
   1448        /* FPU */
   1449        VMSTATE_UINT16(env.fpuc, X86CPU),
   1450        VMSTATE_UINT16(env.fpus_vmstate, X86CPU),
   1451        VMSTATE_UINT16(env.fptag_vmstate, X86CPU),
   1452        VMSTATE_UINT16(env.fpregs_format_vmstate, X86CPU),
   1453
   1454        VMSTATE_STRUCT_ARRAY(env.fpregs, X86CPU, 8, 0, vmstate_fpreg, FPReg),
   1455
   1456        VMSTATE_SEGMENT_ARRAY(env.segs, X86CPU, 6),
   1457        VMSTATE_SEGMENT(env.ldt, X86CPU),
   1458        VMSTATE_SEGMENT(env.tr, X86CPU),
   1459        VMSTATE_SEGMENT(env.gdt, X86CPU),
   1460        VMSTATE_SEGMENT(env.idt, X86CPU),
   1461
   1462        VMSTATE_UINT32(env.sysenter_cs, X86CPU),
   1463        VMSTATE_UINTTL(env.sysenter_esp, X86CPU),
   1464        VMSTATE_UINTTL(env.sysenter_eip, X86CPU),
   1465
   1466        VMSTATE_UINTTL(env.cr[0], X86CPU),
   1467        VMSTATE_UINTTL(env.cr[2], X86CPU),
   1468        VMSTATE_UINTTL(env.cr[3], X86CPU),
   1469        VMSTATE_UINTTL(env.cr[4], X86CPU),
   1470        VMSTATE_UINTTL_ARRAY(env.dr, X86CPU, 8),
   1471        /* MMU */
   1472        VMSTATE_INT32(env.a20_mask, X86CPU),
   1473        /* XMM */
   1474        VMSTATE_UINT32(env.mxcsr, X86CPU),
   1475        VMSTATE_XMM_REGS(env.xmm_regs, X86CPU, 0),
   1476
   1477#ifdef TARGET_X86_64
   1478        VMSTATE_UINT64(env.efer, X86CPU),
   1479        VMSTATE_UINT64(env.star, X86CPU),
   1480        VMSTATE_UINT64(env.lstar, X86CPU),
   1481        VMSTATE_UINT64(env.cstar, X86CPU),
   1482        VMSTATE_UINT64(env.fmask, X86CPU),
   1483        VMSTATE_UINT64(env.kernelgsbase, X86CPU),
   1484#endif
   1485        VMSTATE_UINT32(env.smbase, X86CPU),
   1486
   1487        VMSTATE_UINT64(env.pat, X86CPU),
   1488        VMSTATE_UINT32(env.hflags2, X86CPU),
   1489
   1490        VMSTATE_UINT64(env.vm_hsave, X86CPU),
   1491        VMSTATE_UINT64(env.vm_vmcb, X86CPU),
   1492        VMSTATE_UINT64(env.tsc_offset, X86CPU),
   1493        VMSTATE_UINT64(env.intercept, X86CPU),
   1494        VMSTATE_UINT16(env.intercept_cr_read, X86CPU),
   1495        VMSTATE_UINT16(env.intercept_cr_write, X86CPU),
   1496        VMSTATE_UINT16(env.intercept_dr_read, X86CPU),
   1497        VMSTATE_UINT16(env.intercept_dr_write, X86CPU),
   1498        VMSTATE_UINT32(env.intercept_exceptions, X86CPU),
   1499        VMSTATE_UINT8(env.v_tpr, X86CPU),
   1500        /* MTRRs */
   1501        VMSTATE_UINT64_ARRAY(env.mtrr_fixed, X86CPU, 11),
   1502        VMSTATE_UINT64(env.mtrr_deftype, X86CPU),
   1503        VMSTATE_MTRR_VARS(env.mtrr_var, X86CPU, MSR_MTRRcap_VCNT, 8),
   1504        /* KVM-related states */
   1505        VMSTATE_INT32(env.interrupt_injected, X86CPU),
   1506        VMSTATE_UINT32(env.mp_state, X86CPU),
   1507        VMSTATE_UINT64(env.tsc, X86CPU),
   1508        VMSTATE_INT32(env.exception_nr, X86CPU),
   1509        VMSTATE_UINT8(env.soft_interrupt, X86CPU),
   1510        VMSTATE_UINT8(env.nmi_injected, X86CPU),
   1511        VMSTATE_UINT8(env.nmi_pending, X86CPU),
   1512        VMSTATE_UINT8(env.has_error_code, X86CPU),
   1513        VMSTATE_UINT32(env.sipi_vector, X86CPU),
   1514        /* MCE */
   1515        VMSTATE_UINT64(env.mcg_cap, X86CPU),
   1516        VMSTATE_UINT64(env.mcg_status, X86CPU),
   1517        VMSTATE_UINT64(env.mcg_ctl, X86CPU),
   1518        VMSTATE_UINT64_ARRAY(env.mce_banks, X86CPU, MCE_BANKS_DEF * 4),
   1519        /* rdtscp */
   1520        VMSTATE_UINT64(env.tsc_aux, X86CPU),
   1521        /* KVM pvclock msr */
   1522        VMSTATE_UINT64(env.system_time_msr, X86CPU),
   1523        VMSTATE_UINT64(env.wall_clock_msr, X86CPU),
   1524        /* XSAVE related fields */
   1525        VMSTATE_UINT64_V(env.xcr0, X86CPU, 12),
   1526        VMSTATE_UINT64_V(env.xstate_bv, X86CPU, 12),
   1527        VMSTATE_YMMH_REGS_VARS(env.xmm_regs, X86CPU, 0, 12),
   1528        VMSTATE_END_OF_LIST()
   1529        /* The above list is not sorted /wrt version numbers, watch out! */
   1530    },
   1531    .subsections = (const VMStateDescription*[]) {
   1532        &vmstate_exception_info,
   1533        &vmstate_async_pf_msr,
   1534        &vmstate_async_pf_int_msr,
   1535        &vmstate_pv_eoi_msr,
   1536        &vmstate_steal_time_msr,
   1537        &vmstate_poll_control_msr,
   1538        &vmstate_fpop_ip_dp,
   1539        &vmstate_msr_tsc_adjust,
   1540        &vmstate_msr_tscdeadline,
   1541        &vmstate_msr_ia32_misc_enable,
   1542        &vmstate_msr_ia32_feature_control,
   1543        &vmstate_msr_architectural_pmu,
   1544        &vmstate_mpx,
   1545        &vmstate_msr_hyperv_hypercall,
   1546        &vmstate_msr_hyperv_vapic,
   1547        &vmstate_msr_hyperv_time,
   1548        &vmstate_msr_hyperv_crash,
   1549        &vmstate_msr_hyperv_runtime,
   1550        &vmstate_msr_hyperv_synic,
   1551        &vmstate_msr_hyperv_stimer,
   1552        &vmstate_msr_hyperv_reenlightenment,
   1553        &vmstate_avx512,
   1554        &vmstate_xss,
   1555        &vmstate_umwait,
   1556        &vmstate_tsc_khz,
   1557        &vmstate_msr_smi_count,
   1558        &vmstate_pkru,
   1559        &vmstate_pkrs,
   1560        &vmstate_spec_ctrl,
   1561        &vmstate_mcg_ext_ctl,
   1562        &vmstate_msr_intel_pt,
   1563        &vmstate_msr_virt_ssbd,
   1564        &vmstate_svm_npt,
   1565        &vmstate_svm_guest,
   1566#ifndef TARGET_X86_64
   1567        &vmstate_efer32,
   1568#endif
   1569#ifdef CONFIG_KVM
   1570        &vmstate_nested_state,
   1571#endif
   1572        &vmstate_msr_tsx_ctrl,
   1573        &vmstate_msr_intel_sgx,
   1574        NULL
   1575    }
   1576};