VirtualBox

Changeset 39307 in vbox for trunk/src/VBox/Devices/PC


Ignore:
Timestamp:
Nov 15, 2011 1:46:46 PM (13 years ago)
Author:
vboxsync
svn:sync-xref-src-repo-rev:
74865
Message:

DevIoApic.cpp: Make sure the 'id' have the same value after reset as on power on (was: cCpus on power on, 0 on reset). Cleanups.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/src/VBox/Devices/PC/DevIoApic.cpp

    r39136 r39307  
    55
    66/*
    7  * Copyright (C) 2006-2010 Oracle Corporation
     7 * Copyright (C) 2006-2011 Oracle Corporation
    88 *
    99 * This file is part of VirtualBox Open Source Edition (OSE), as
     
    7272#define IOAPIC_UNLOCK(pThis) (pThis)->CTX_SUFF(pIoApicHlp)->pfnUnlock((pThis)->CTX_SUFF(pDevIns))
    7373
    74 
    75 #define foreach_apic(pDev, mask, code)                    \
    76     do {                                                  \
    77         APICState *apic = (pDev)->CTX_SUFF(paLapics);     \
    78         for (uint32_t i = 0; i < (pDev)->cCpus; i++)      \
    79         {                                                 \
    80             if (mask & (1 << (apic->id)))                 \
    81             {                                             \
    82                 code;                                     \
    83             }                                             \
    84             apic++;                                       \
    85         }                                                 \
    86     } while (0)
    87 
    88 # define set_bit(pvBitmap, iBit)    ASMBitSet(pvBitmap, iBit)
    89 # define reset_bit(pvBitmap, iBit)  ASMBitClear(pvBitmap, iBit)
    90 # define fls_bit(value)             (ASMBitLastSetU32(value) - 1)
    91 # define ffs_bit(value)             (ASMBitFirstSetU32(value) - 1)
    92 
    9374#define DEBUG_IOAPIC
    9475#define IOAPIC_NUM_PINS                 0x18
     
    9879*   Structures and Typedefs                                                    *
    9980*******************************************************************************/
    100 struct IOAPICState {
    101     uint8_t id;
    102     uint8_t ioregsel;
    103 
    104     uint32_t irr;
    105     uint64_t ioredtbl[IOAPIC_NUM_PINS];
     81struct IOAPICState
     82{
     83    uint8_t                 id;
     84    uint8_t                 ioregsel;
     85    uint8_t                 cCpus;
     86
     87    uint32_t                irr;
     88    uint64_t                ioredtbl[IOAPIC_NUM_PINS];
    10689
    10790    /** The device instance - R3 Ptr. */
     
    139122
    140123
    141 static void ioapic_service(IOAPICState *s)
     124static void ioapic_service(IOAPICState *pThis)
    142125{
    143126    uint8_t i;
     
    151134    uint8_t polarity;
    152135
    153     for (i = 0; i < IOAPIC_NUM_PINS; i++) {
     136    for (i = 0; i < IOAPIC_NUM_PINS; i++)
     137    {
    154138        mask = 1 << i;
    155         if (s->irr & mask) {
    156             entry = s->ioredtbl[i];
    157             if (!(entry & APIC_LVT_MASKED)) {
     139        if (pThis->irr & mask)
     140        {
     141            entry = pThis->ioredtbl[i];
     142            if (!(entry & APIC_LVT_MASKED))
     143            {
    158144                trig_mode = ((entry >> 15) & 1);
    159145                dest = entry >> 56;
     
    162148                polarity = (entry >> 13) & 1;
    163149                if (trig_mode == APIC_TRIGGER_EDGE)
    164                     s->irr &= ~mask;
     150                    pThis->irr &= ~mask;
    165151                if (delivery_mode == APIC_DM_EXTINT)
    166152                    /* malc: i'm still not so sure about ExtINT delivery */
     
    172158                    vector = entry & 0xff;
    173159
    174                 int rc = s->CTX_SUFF(pIoApicHlp)->pfnApicBusDeliver(s->CTX_SUFF(pDevIns),
    175                                                            dest,
    176                                                            dest_mode,
    177                                                            delivery_mode,
    178                                                            vector,
    179                                                            polarity,
    180                                                            trig_mode);
     160                int rc = pThis->CTX_SUFF(pIoApicHlp)->pfnApicBusDeliver(pThis->CTX_SUFF(pDevIns),
     161                                                                        dest,
     162                                                                        dest_mode,
     163                                                                        delivery_mode,
     164                                                                        vector,
     165                                                                        polarity,
     166                                                                        trig_mode);
    181167                /* We must be sure that attempts to reschedule in R3
    182168                   never get here */
     
    190176static void ioapic_set_irq(void *opaque, int vector, int level)
    191177{
    192     IOAPICState *s = (IOAPICState*)opaque;
    193 
    194     if (vector >= 0 && vector < IOAPIC_NUM_PINS) {
     178    IOAPICState *pThis = (IOAPICState*)opaque;
     179
     180    if (vector >= 0 && vector < IOAPIC_NUM_PINS)
     181    {
    195182        uint32_t mask = 1 << vector;
    196         uint64_t entry = s->ioredtbl[vector];
    197 
    198         if ((entry >> 15) & 1) {
     183        uint64_t entry = pThis->ioredtbl[vector];
     184
     185        if ((entry >> 15) & 1)
     186        {
    199187            /* level triggered */
    200             if (level) {
    201                 s->irr |= mask;
    202                 ioapic_service(s);
    203                 if ((level & PDM_IRQ_LEVEL_FLIP_FLOP) == PDM_IRQ_LEVEL_FLIP_FLOP) {
    204                     s->irr &= ~mask;
    205                 }
    206             } else {
    207                 s->irr &= ~mask;
     188            if (level)
     189            {
     190                pThis->irr |= mask;
     191                ioapic_service(pThis);
     192                if ((level & PDM_IRQ_LEVEL_FLIP_FLOP) == PDM_IRQ_LEVEL_FLIP_FLOP)
     193                    pThis->irr &= ~mask;
    208194            }
    209         } else {
     195            else
     196                pThis->irr &= ~mask;
     197        }
     198        else
     199        {
    210200            /* edge triggered */
    211             if (level) {
    212                 s->irr |= mask;
    213                 ioapic_service(s);
     201            if (level)
     202            {
     203                pThis->irr |= mask;
     204                ioapic_service(pThis);
    214205            }
    215206        }
     
    219210static uint32_t ioapic_mem_readl(void *opaque, RTGCPHYS addr)
    220211{
    221     IOAPICState *s = (IOAPICState*)opaque;
    222     int index;
     212    IOAPICState *pThis = (IOAPICState*)opaque;
    223213    uint32_t val = 0;
    224214
    225215    addr &= 0xff;
    226     if (addr == 0x00) {
    227         val = s->ioregsel;
    228     } else if (addr == 0x10) {
    229         switch (s->ioregsel) {
     216    if (addr == 0x00)
     217        val = pThis->ioregsel;
     218    else if (addr == 0x10)
     219    {
     220        switch (pThis->ioregsel)
     221        {
    230222            case 0x00:
    231                 val = s->id << 24;
     223                val = pThis->id << 24;
    232224                break;
     225
    233226            case 0x01:
    234227                val = 0x11 | ((IOAPIC_NUM_PINS - 1) << 16); /* version 0x11 */
    235228                break;
     229
    236230            case 0x02:
    237231                val = 0;
    238232                break;
     233
    239234            default:
    240                 index = (s->ioregsel - 0x10) >> 1;
    241                 if (index >= 0 && index < IOAPIC_NUM_PINS) {
    242                     if (s->ioregsel & 1)
    243                         val = s->ioredtbl[index] >> 32;
     235            {
     236                int index = (pThis->ioregsel - 0x10) >> 1;
     237                if (index >= 0 && index < IOAPIC_NUM_PINS)
     238                {
     239                    if (pThis->ioregsel & 1)
     240                        val = pThis->ioredtbl[index] >> 32;
    244241                    else
    245                         val = s->ioredtbl[index] & 0xffffffff;
     242                        val = pThis->ioredtbl[index] & 0xffffffff;
    246243                }
     244                else
     245                    val = 0;
     246                break;
     247            }
    247248        }
    248249#ifdef DEBUG_IOAPIC
    249         Log(("I/O APIC read: %08x = %08x\n", s->ioregsel, val));
     250        Log(("I/O APIC read: %08x = %08x\n", pThis->ioregsel, val));
    250251#endif
    251252    }
     253    else
     254        val = 0;
    252255    return val;
    253256}
     
    255258static void ioapic_mem_writel(void *opaque, RTGCPHYS addr, uint32_t val)
    256259{
    257     IOAPICState *s = (IOAPICState*)opaque;
     260    IOAPICState *pThis = (IOAPICState*)opaque;
    258261    int index;
    259262
    260263    addr &= 0xff;
    261     if (addr == 0x00)  {
    262         s->ioregsel = val;
     264    if (addr == 0x00)
     265    {
     266        pThis->ioregsel = val;
    263267        return;
    264     } else if (addr == 0x10) {
     268    }
     269
     270    if (addr == 0x10)
     271    {
    265272#ifdef DEBUG_IOAPIC
    266         Log(("I/O APIC write: %08x = %08x\n", s->ioregsel, val));
     273        Log(("I/O APIC write: %08x = %08x\n", pThis->ioregsel, val));
    267274#endif
    268         switch (s->ioregsel) {
     275        switch (pThis->ioregsel)
     276        {
    269277            case 0x00:
    270                 s->id = (val >> 24) & 0xff;
     278                pThis->id = (val >> 24) & 0xff;
    271279                return;
     280
    272281            case 0x01:
    273282            case 0x02:
    274283                return;
     284
    275285            default:
    276                 index = (s->ioregsel - 0x10) >> 1;
    277                 if (index >= 0 && index < IOAPIC_NUM_PINS) {
    278                     if (s->ioregsel & 1) {
    279                         s->ioredtbl[index] &= 0xffffffff;
    280                         s->ioredtbl[index] |= (uint64_t)val << 32;
    281                     } else {
     286                index = (pThis->ioregsel - 0x10) >> 1;
     287                if (index >= 0 && index < IOAPIC_NUM_PINS)
     288                {
     289                    if (pThis->ioregsel & 1)
     290                    {
     291                        pThis->ioredtbl[index] &= 0xffffffff;
     292                        pThis->ioredtbl[index] |= (uint64_t)val << 32;
     293                    }
     294                    else
     295                    {
    282296                        /* According to IOAPIC spec, vectors should be from 0x10 to 0xfe */
    283297                        uint8_t vec = val & 0xff;
    284                         if ((val & APIC_LVT_MASKED) ||
    285                             ((vec >= 0x10) && (vec < 0xff)))
     298                        if (   (val & APIC_LVT_MASKED)
     299                            || (vec >= 0x10 && vec < 0xff) )
    286300                        {
    287                             s->ioredtbl[index] &= ~0xffffffffULL;
    288                             s->ioredtbl[index] |= val;
     301                            pThis->ioredtbl[index] &= ~0xffffffffULL;
     302                            pThis->ioredtbl[index] |= val;
    289303                        }
    290304                        else
     
    292306                            /*
    293307                             * Linux 2.6 kernels has pretty strange function
    294                              * unlock_ExtINT_logic() which writes
    295                              * absolutely bogus (all 0) value into the vector
    296                              * with pretty vague explanation why.
    297                              * So we just ignore such writes.
     308                             * unlock_ExtINT_logic() which writes absolutely
     309                             * bogus (all 0) value into the vector with pretty
     310                             * vague explanation why.  So we just ignore such
     311                             * writes.
    298312                             */
    299                             LogRel(("IOAPIC GUEST BUG: bad vector writing %x(sel=%x) to %d\n", val, s->ioregsel, index));
     313                            LogRel(("IOAPIC GUEST BUG: bad vector writing %x(sel=%x) to %d\n", val, pThis->ioregsel, index));
    300314                        }
    301315                    }
    302                     ioapic_service(s);
     316                    ioapic_service(pThis);
    303317                }
    304318        }
     
    306320}
    307321
    308 #ifdef IN_RING3
    309 
    310 static void ioapic_save(SSMHANDLE *f, void *opaque)
    311 {
    312     IOAPICState *s = (IOAPICState*)opaque;
    313     int i;
    314 
    315     SSMR3PutU8(f, s->id);
    316     SSMR3PutU8(f, s->ioregsel);
    317     for (i = 0; i < IOAPIC_NUM_PINS; i++) {
    318         SSMR3PutU64(f, s->ioredtbl[i]);
    319     }
    320 }
    321 
    322 static int ioapic_load(SSMHANDLE *f, void *opaque, int version_id)
    323 {
    324     IOAPICState *s = (IOAPICState*)opaque;
    325     int i;
    326 
    327     if (version_id != 1)
    328         return VERR_SSM_UNSUPPORTED_DATA_UNIT_VERSION;
    329 
    330     SSMR3GetU8(f, &s->id);
    331     SSMR3GetU8(f, &s->ioregsel);
    332     for (i = 0; i < IOAPIC_NUM_PINS; i++) {
    333         SSMR3GetU64(f, &s->ioredtbl[i]);
    334     }
    335     return 0;
    336 }
    337 
    338 static void ioapic_reset(void *opaque)
    339 {
    340     IOAPICState *s = (IOAPICState*)opaque;
    341     PPDMDEVINSR3        pDevIns    = s->pDevInsR3;
    342     PCPDMIOAPICHLPR3    pIoApicHlp = s->pIoApicHlpR3;
    343     int i;
    344 
    345     memset(s, 0, sizeof(*s));
    346     for(i = 0; i < IOAPIC_NUM_PINS; i++)
    347         s->ioredtbl[i] = 1 << 16; /* mask LVT */
    348 
    349     if (pDevIns)
    350     {
    351         s->pDevInsR3 = pDevIns;
    352         s->pDevInsRC = PDMDEVINS_2_RCPTR(pDevIns);
    353         s->pDevInsR0 = PDMDEVINS_2_R0PTR(pDevIns);
    354     }
    355     if (pIoApicHlp)
    356     {
    357         s->pIoApicHlpR3 = pIoApicHlp;
    358         s->pIoApicHlpRC = s->pIoApicHlpR3->pfnGetRCHelpers(pDevIns);
    359         s->pIoApicHlpR0 = s->pIoApicHlpR3->pfnGetR0Helpers(pDevIns);
    360     }
    361 }
    362 
    363 #endif /* IN_RING3 */
    364 
    365 
    366322/* IOAPIC */
    367323
    368324PDMBOTHCBDECL(int) ioapicMMIORead(PPDMDEVINS pDevIns, void *pvUser, RTGCPHYS GCPhysAddr, void *pv, unsigned cb)
    369325{
    370     IOAPICState *s = PDMINS_2_DATA(pDevIns, IOAPICState *);
    371     IOAPIC_LOCK(s, VINF_IOM_HC_MMIO_READ);
    372 
    373     STAM_COUNTER_INC(&CTXSUFF(s->StatMMIORead));
    374     switch (cb) {
    375     case 1:
    376         *(uint8_t *)pv = ioapic_mem_readl(s, GCPhysAddr);
    377         break;
    378 
    379     case 2:
    380         *(uint16_t *)pv = ioapic_mem_readl(s, GCPhysAddr);
    381         break;
    382 
    383     case 4:
    384         *(uint32_t *)pv = ioapic_mem_readl(s, GCPhysAddr);
    385         break;
    386 
    387     default:
    388         AssertReleaseMsgFailed(("cb=%d\n", cb)); /* for now we assume simple accesses. */
    389         IOAPIC_UNLOCK(s);
    390         return VERR_INTERNAL_ERROR;
    391     }
    392     IOAPIC_UNLOCK(s);
     326    IOAPICState *pThis = PDMINS_2_DATA(pDevIns, IOAPICState *);
     327    IOAPIC_LOCK(pThis, VINF_IOM_HC_MMIO_READ);
     328
     329    STAM_COUNTER_INC(&CTXSUFF(pThis->StatMMIORead));
     330    switch (cb)
     331    {
     332        case 1:
     333            *(uint8_t *)pv = ioapic_mem_readl(pThis, GCPhysAddr);
     334            break;
     335
     336        case 2:
     337            *(uint16_t *)pv = ioapic_mem_readl(pThis, GCPhysAddr);
     338            break;
     339
     340        case 4:
     341            *(uint32_t *)pv = ioapic_mem_readl(pThis, GCPhysAddr);
     342            break;
     343
     344        default:
     345            AssertReleaseMsgFailed(("cb=%d\n", cb)); /* for now we assume simple accesses. */
     346            IOAPIC_UNLOCK(pThis);
     347            return VERR_INTERNAL_ERROR;
     348    }
     349    IOAPIC_UNLOCK(pThis);
    393350    return VINF_SUCCESS;
    394351}
     
    396353PDMBOTHCBDECL(int) ioapicMMIOWrite(PPDMDEVINS pDevIns, void *pvUser, RTGCPHYS GCPhysAddr, void const *pv, unsigned cb)
    397354{
    398     IOAPICState *s = PDMINS_2_DATA(pDevIns, IOAPICState *);
    399 
    400     STAM_COUNTER_INC(&CTXSUFF(s->StatMMIOWrite));
    401     IOAPIC_LOCK(s, VINF_IOM_HC_MMIO_WRITE);
     355    IOAPICState *pThis = PDMINS_2_DATA(pDevIns, IOAPICState *);
     356
     357    STAM_COUNTER_INC(&CTXSUFF(pThis->StatMMIOWrite));
     358    IOAPIC_LOCK(pThis, VINF_IOM_HC_MMIO_WRITE);
    402359    switch (cb)
    403360    {
    404         case 1: ioapic_mem_writel(s, GCPhysAddr, *(uint8_t  const *)pv); break;
    405         case 2: ioapic_mem_writel(s, GCPhysAddr, *(uint16_t const *)pv); break;
    406         case 4: ioapic_mem_writel(s, GCPhysAddr, *(uint32_t const *)pv); break;
     361        case 1: ioapic_mem_writel(pThis, GCPhysAddr, *(uint8_t  const *)pv); break;
     362        case 2: ioapic_mem_writel(pThis, GCPhysAddr, *(uint16_t const *)pv); break;
     363        case 4: ioapic_mem_writel(pThis, GCPhysAddr, *(uint32_t const *)pv); break;
    407364
    408365        default:
    409             IOAPIC_UNLOCK(s);
     366            IOAPIC_UNLOCK(pThis);
    410367            AssertReleaseMsgFailed(("cb=%d\n", cb)); /* for now we assume simple accesses. */
    411368            return VERR_INTERNAL_ERROR;
    412369    }
    413     IOAPIC_UNLOCK(s);
     370    IOAPIC_UNLOCK(pThis);
    414371    return VINF_SUCCESS;
    415372}
     
    417374PDMBOTHCBDECL(void) ioapicSetIrq(PPDMDEVINS pDevIns, int iIrq, int iLevel)
    418375{
    419     /* PDM lock is taken here; @todo add assertion */
     376    /* PDM lock is taken here; */ /** @todo add assertion */
    420377    IOAPICState *pThis = PDMINS_2_DATA(pDevIns, IOAPICState *);
    421378    STAM_COUNTER_INC(&pThis->CTXSUFF(StatSetIrq));
     
    466423static DECLCALLBACK(void) ioapicInfo(PPDMDEVINS pDevIns, PCDBGFINFOHLP pHlp, const char *pszArgs)
    467424{
    468     IOAPICState *s = PDMINS_2_DATA(pDevIns, IOAPICState *);
    469     uint32_t    val;
    470     unsigned    i;
    471     unsigned    max_redir;
    472 
    473     pHlp->pfnPrintf(pHlp, "I/O APIC at %08X:\n", 0xfec00000);
    474     val = s->id << 24;  /* Would be nice to call ioapic_mem_readl() directly, but that's not so simple. */
    475     pHlp->pfnPrintf(pHlp, "  IOAPICID  : %08X\n", val);
    476     pHlp->pfnPrintf(pHlp, "    APIC ID = %02X\n", (val >> 24) & 0xff);
    477     val = 0x11 | ((IOAPIC_NUM_PINS - 1) << 16);
    478     max_redir = (val >> 16) & 0xff;
    479     pHlp->pfnPrintf(pHlp, "  IOAPICVER : %08X\n", val);
    480     pHlp->pfnPrintf(pHlp, "    version = %02X\n", val & 0xff);
    481     pHlp->pfnPrintf(pHlp, "    redirs  = %d\n", ((val >> 16) & 0xff) + 1);
    482     val = 0;
    483     pHlp->pfnPrintf(pHlp, "  IOAPICARB : %08X\n", val);
    484     pHlp->pfnPrintf(pHlp, "    arb ID  = %02X\n", (val >> 24) & 0xff);
    485     Assert(sizeof(s->ioredtbl) / sizeof(s->ioredtbl[0]) > max_redir);
     425    IOAPICState *pThis = PDMINS_2_DATA(pDevIns, IOAPICState *);
     426    uint32_t     uVal;
     427
     428    pHlp->pfnPrintf(pHlp, "I/O APIC at %08x:\n", 0xfec00000);
     429    uVal = pThis->id << 24;  /* Would be nice to call ioapic_mem_readl() directly, but that's not so simple. */
     430    pHlp->pfnPrintf(pHlp, "  IOAPICID  : %08x\n", uVal);
     431    pHlp->pfnPrintf(pHlp, "    APIC ID = %02x\n", (uVal >> 24) & 0xff);
     432    uVal = 0x11 | ((IOAPIC_NUM_PINS - 1) << 16);
     433    unsigned max_redir = RT_BYTE3(uVal);
     434    pHlp->pfnPrintf(pHlp, "  IOAPICVER : %08x\n", uVal);
     435    pHlp->pfnPrintf(pHlp, "    version = %02x\n", uVal & 0xff);
     436    pHlp->pfnPrintf(pHlp, "    redirs  = %d\n", RT_BYTE3(uVal) + 1);
     437    uVal = 0;
     438    pHlp->pfnPrintf(pHlp, "  IOAPICARB : %08x\n", uVal);
     439    pHlp->pfnPrintf(pHlp, "    arb ID  = %02x\n", RT_BYTE4(uVal) & 0xff);
     440    Assert(sizeof(pThis->ioredtbl) / sizeof(pThis->ioredtbl[0]) > max_redir);
    486441    pHlp->pfnPrintf(pHlp, "I/O redirection table\n");
    487442    pHlp->pfnPrintf(pHlp, " idx dst_mode dst_addr mask trigger rirr polarity dlvr_st dlvr_mode vector\n");
    488     for (i = 0; i <= max_redir; ++i)
    489     {
    490         static const char *dmodes[] = { "Fixed ", "LowPri", "SMI   ", "Resrvd",
    491                                         "NMI   ", "INIT  ", "Resrvd", "ExtINT" };
    492 
    493         pHlp->pfnPrintf(pHlp, "  %02d   %s      %02X     %d    %s   %d   %s  %s     %s   %3d (%016llX)\n",
     443    for (unsigned i = 0; i <= max_redir; ++i)
     444    {
     445        static const char * const s_apszDModes[] =
     446        {
     447            "Fixed ", "LowPri", "SMI   ", "Resrvd", "NMI   ", "INIT  ", "Resrvd", "ExtINT"
     448        };
     449
     450        pHlp->pfnPrintf(pHlp, "  %02d   %s      %02x     %d    %s   %d   %s  %s     %s   %3d (%016llx)\n",
    494451                        i,
    495                         s->ioredtbl[i] & (1 << 11) ? "log " : "phys",           /* dest mode */
    496                         (int)(s->ioredtbl[i] >> 56),                            /* dest addr */
    497                         (int)(s->ioredtbl[i] >> 16) & 1,                        /* mask */
    498                         s->ioredtbl[i] & (1 << 15) ? "level" : "edge ",         /* trigger */
    499                         (int)(s->ioredtbl[i] >> 14) & 1,                        /* remote IRR */
    500                         s->ioredtbl[i] & (1 << 13) ? "activelo" : "activehi",   /* polarity */
    501                         s->ioredtbl[i] & (1 << 12) ? "pend" : "idle",           /* delivery status */
    502                         dmodes[(s->ioredtbl[i] >> 8) & 0x07],                   /* delivery mode */
    503                         (int)s->ioredtbl[i] & 0xff,                             /* vector */
    504                         s->ioredtbl[i]                                          /* entire register */
     452                        pThis->ioredtbl[i] & (1 << 11) ? "log " : "phys",           /* dest mode */
     453                        (int)(pThis->ioredtbl[i] >> 56),                            /* dest addr */
     454                        (int)(pThis->ioredtbl[i] >> 16) & 1,                        /* mask */
     455                        pThis->ioredtbl[i] & (1 << 15) ? "level" : "edge ",         /* trigger */
     456                        (int)(pThis->ioredtbl[i] >> 14) & 1,                        /* remote IRR */
     457                        pThis->ioredtbl[i] & (1 << 13) ? "activelo" : "activehi",   /* polarity */
     458                        pThis->ioredtbl[i] & (1 << 12) ? "pend" : "idle",           /* delivery status */
     459                        s_apszDModes[(pThis->ioredtbl[i] >> 8) & 0x07],             /* delivery mode */
     460                        (int)pThis->ioredtbl[i] & 0xff,                             /* vector */
     461                        pThis->ioredtbl[i]                                          /* entire register */
    505462                        );
    506463    }
     
    512469static DECLCALLBACK(int) ioapicSaveExec(PPDMDEVINS pDevIns, PSSMHANDLE pSSM)
    513470{
    514     IOAPICState *s = PDMINS_2_DATA(pDevIns, IOAPICState *);
    515     ioapic_save(pSSM, s);
     471    IOAPICState *pThis = PDMINS_2_DATA(pDevIns, IOAPICState *);
     472
     473    SSMR3PutU8(pSSM, pThis->id);
     474    SSMR3PutU8(pSSM, pThis->ioregsel);
     475    for (unsigned i = 0; i < IOAPIC_NUM_PINS; i++)
     476        SSMR3PutU64(pSSM, pThis->ioredtbl[i]);
     477
    516478    return VINF_SUCCESS;
    517479}
     
    522484static DECLCALLBACK(int) ioapicLoadExec(PPDMDEVINS pDevIns, PSSMHANDLE pSSM, uint32_t uVersion, uint32_t uPass)
    523485{
    524     IOAPICState *s = PDMINS_2_DATA(pDevIns, IOAPICState *);
    525 
    526     if (ioapic_load(pSSM, s, uVersion)) {
    527         AssertFailed();
     486    IOAPICState *pThis = PDMINS_2_DATA(pDevIns, IOAPICState *);
     487    if (uVersion != 1)
    528488        return VERR_SSM_UNSUPPORTED_DATA_UNIT_VERSION;
    529     }
     489
     490    SSMR3GetU8(pSSM, &pThis->id);
     491    SSMR3GetU8(pSSM, &pThis->ioregsel);
     492    for (unsigned i = 0; i < IOAPIC_NUM_PINS; i++)
     493        SSMR3GetU64(pSSM, &pThis->ioredtbl[i]);
     494
    530495    Assert(uPass == SSM_PASS_FINAL); NOREF(uPass);
    531 
    532496    return VINF_SUCCESS;
    533497}
     
    538502static DECLCALLBACK(void) ioapicReset(PPDMDEVINS pDevIns)
    539503{
    540     IOAPICState *s = PDMINS_2_DATA(pDevIns, IOAPICState *);
    541     s->pIoApicHlpR3->pfnLock(pDevIns, VERR_INTERNAL_ERROR);
    542     ioapic_reset(s);
    543     IOAPIC_UNLOCK(s);
     504    IOAPICState        *pThis = PDMINS_2_DATA(pDevIns, IOAPICState *);
     505    pThis->pIoApicHlpR3->pfnLock(pDevIns, VERR_INTERNAL_ERROR);
     506
     507    pThis->id       = pThis->cCpus;
     508    pThis->ioregsel = 0;
     509    pThis->irr      = 0;
     510    for (unsigned i = 0; i < IOAPIC_NUM_PINS; i++)
     511        pThis->ioredtbl[i] = 1 << 16; /* mask LVT */
     512
     513    IOAPIC_UNLOCK(pThis);
    544514}
    545515
     
    549519static DECLCALLBACK(void) ioapicRelocate(PPDMDEVINS pDevIns, RTGCINTPTR offDelta)
    550520{
    551     IOAPICState *s = PDMINS_2_DATA(pDevIns, IOAPICState *);
    552     s->pDevInsRC    = PDMDEVINS_2_RCPTR(pDevIns);
    553     s->pIoApicHlpRC = s->pIoApicHlpR3->pfnGetRCHelpers(pDevIns);
     521    IOAPICState *pThis = PDMINS_2_DATA(pDevIns, IOAPICState *);
     522    pThis->pDevInsRC    = PDMDEVINS_2_RCPTR(pDevIns);
     523    pThis->pIoApicHlpRC = pThis->pIoApicHlpR3->pfnGetRCHelpers(pDevIns);
    554524}
    555525
     
    559529static DECLCALLBACK(int) ioapicConstruct(PPDMDEVINS pDevIns, int iInstance, PCFGMNODE pCfg)
    560530{
    561     IOAPICState *s = PDMINS_2_DATA(pDevIns, IOAPICState *);
    562     PDMIOAPICREG IoApicReg;
    563     bool         fGCEnabled;
    564     bool         fR0Enabled;
    565     int          rc;
    566     uint32_t     cCpus;
    567 
     531    IOAPICState *pThis = PDMINS_2_DATA(pDevIns, IOAPICState *);
    568532    Assert(iInstance == 0);
    569533
     
    571535     * Validate and read the configuration.
    572536     */
    573     if (!CFGMR3AreValuesValid(pCfg,
    574                               "GCEnabled\0"
    575                               "R0Enabled\0"
    576                               "NumCPUs\0"))
    577         return VERR_PDM_DEVINS_UNKNOWN_CFG_VALUES;
    578 
    579     rc = CFGMR3QueryBoolDef(pCfg, "GCEnabled", &fGCEnabled, true);
    580     if (RT_FAILURE(rc))
    581         return PDMDEV_SET_ERROR(pDevIns, rc,
    582                                 N_("Configuration error: Failed to query boolean value \"GCEnabled\""));
    583 
    584     rc = CFGMR3QueryBoolDef(pCfg, "R0Enabled", &fR0Enabled, true);
    585     if (RT_FAILURE(rc))
    586         return PDMDEV_SET_ERROR(pDevIns, rc,
    587                                 N_("Configuration error: Failed to query boolean value \"R0Enabled\""));
    588 
    589     rc = CFGMR3QueryU32Def(pCfg, "NumCPUs", &cCpus, 1);
     537    PDMDEV_VALIDATE_CONFIG_RETURN(pDevIns, "NumCPUs|RZEnabled", "");
     538
     539    uint32_t cCpus;
     540    int rc = CFGMR3QueryU32Def(pCfg, "NumCPUs", &cCpus, 1);
    590541    if (RT_FAILURE(rc))
    591542        return PDMDEV_SET_ERROR(pDevIns, rc,
    592543                                N_("Configuration error: Failed to query integer value \"NumCPUs\""));
    593 
    594     Log(("IOAPIC: fR0Enabled=%RTbool fGCEnabled=%RTbool\n", fR0Enabled, fGCEnabled));
     544    if (cCpus > UINT8_MAX - 1)
     545        return PDMDevHlpVMSetError(pDevIns, rc, RT_SRC_POS,
     546                                   N_("Configuration error: Max %u CPUs, %u specified"), UINT8_MAX - 1, cCpus);
     547
     548    bool fRZEnabled;
     549    rc = CFGMR3QueryBoolDef(pCfg, "RZEnabled", &fRZEnabled, true);
     550    if (RT_FAILURE(rc))
     551        return PDMDEV_SET_ERROR(pDevIns, rc,
     552                                N_("Configuration error: Failed to query boolean value \"RZEnabled\""));
     553
     554    Log(("IOAPIC: cCpus=%u fRZEnabled=%RTbool\n", cCpus, fRZEnabled));
    595555
    596556    /*
    597557     * Initialize the state data.
    598558     */
    599     s->pDevInsR3 = pDevIns;
    600     s->pDevInsR0 = PDMDEVINS_2_R0PTR(pDevIns);
    601     s->pDevInsRC = PDMDEVINS_2_RCPTR(pDevIns);
    602     ioapic_reset(s);
    603     s->id = cCpus;
     559    pThis->pDevInsR3 = pDevIns;
     560    pThis->pDevInsR0 = PDMDEVINS_2_R0PTR(pDevIns);
     561    pThis->pDevInsRC = PDMDEVINS_2_RCPTR(pDevIns);
     562    pThis->cCpus = (uint8_t)cCpus;
     563    /* (the rest is done by the reset call at the end) */
    604564
    605565    /* PDM provides locking via the IOAPIC helpers. */
     
    610570     * Register the IOAPIC and get helpers.
    611571     */
    612     IoApicReg.u32Version  = PDM_IOAPICREG_VERSION;
    613     IoApicReg.pfnSetIrqR3 = ioapicSetIrq;
    614     IoApicReg.pszSetIrqRC = fGCEnabled ? "ioapicSetIrq" : NULL;
    615     IoApicReg.pszSetIrqR0 = fR0Enabled ? "ioapicSetIrq" : NULL;
     572    PDMIOAPICREG IoApicReg;
     573    IoApicReg.u32Version   = PDM_IOAPICREG_VERSION;
     574    IoApicReg.pfnSetIrqR3  = ioapicSetIrq;
     575    IoApicReg.pszSetIrqRC  = fRZEnabled ? "ioapicSetIrq"  : NULL;
     576    IoApicReg.pszSetIrqR0  = fRZEnabled ? "ioapicSetIrq"  : NULL;
    616577    IoApicReg.pfnSendMsiR3 = ioapicSendMsi;
    617     IoApicReg.pszSendMsiRC = fGCEnabled ? "ioapicSendMsi" : NULL;
    618     IoApicReg.pszSendMsiR0 = fR0Enabled ? "ioapicSendMsi" : NULL;
    619 
    620     rc = PDMDevHlpIOAPICRegister(pDevIns, &IoApicReg, &s->pIoApicHlpR3);
     578    IoApicReg.pszSendMsiRC = fRZEnabled ? "ioapicSendMsi" : NULL;
     579    IoApicReg.pszSendMsiR0 = fRZEnabled ? "ioapicSendMsi" : NULL;
     580
     581    rc = PDMDevHlpIOAPICRegister(pDevIns, &IoApicReg, &pThis->pIoApicHlpR3);
    621582    if (RT_FAILURE(rc))
    622583    {
     
    628589     * Register MMIO callbacks and saved state.
    629590     */
    630     rc = PDMDevHlpMMIORegister(pDevIns, 0xfec00000, 0x1000, s,
     591    rc = PDMDevHlpMMIORegister(pDevIns, UINT32_C(0xfec00000), 0x1000, pThis,
    631592                               IOMMMIO_FLAGS_READ_PASSTHRU | IOMMMIO_FLAGS_WRITE_PASSTHRU,
    632593                               ioapicMMIOWrite, ioapicMMIORead, "I/O APIC Memory");
     
    634595        return rc;
    635596
    636     if (fGCEnabled) {
    637         s->pIoApicHlpRC = s->pIoApicHlpR3->pfnGetRCHelpers(pDevIns);
    638 
    639         rc = PDMDevHlpMMIORegisterRC(pDevIns, 0xfec00000, 0x1000, NIL_RTRCPTR /*pvUser*/, "ioapicMMIOWrite", "ioapicMMIORead");
    640         if (RT_FAILURE(rc))
    641             return rc;
    642     }
    643 
    644     if (fR0Enabled) {
    645         s->pIoApicHlpR0 = s->pIoApicHlpR3->pfnGetR0Helpers(pDevIns);
    646 
    647         rc = PDMDevHlpMMIORegisterR0(pDevIns, 0xfec00000, 0x1000, NIL_RTR0PTR /*pvUser*/,
     597    if (fRZEnabled)
     598    {
     599        pThis->pIoApicHlpRC = pThis->pIoApicHlpR3->pfnGetRCHelpers(pDevIns);
     600        rc = PDMDevHlpMMIORegisterRC(pDevIns, UINT32_C(0xfec00000), 0x1000, NIL_RTRCPTR /*pvUser*/, "ioapicMMIOWrite", "ioapicMMIORead");
     601        AssertRCReturn(rc, rc);
     602
     603        pThis->pIoApicHlpR0 = pThis->pIoApicHlpR3->pfnGetR0Helpers(pDevIns);
     604        rc = PDMDevHlpMMIORegisterR0(pDevIns, UINT32_C(0xfec00000), 0x1000, NIL_RTR0PTR /*pvUser*/,
    648605                                     "ioapicMMIOWrite", "ioapicMMIORead");
    649         if (RT_FAILURE(rc))
    650             return rc;
    651     }
    652 
    653     rc = PDMDevHlpSSMRegister(pDevIns, 1 /* version */, sizeof(*s), ioapicSaveExec, ioapicLoadExec);
     606        AssertRCReturn(rc, rc);
     607    }
     608
     609    rc = PDMDevHlpSSMRegister(pDevIns, 1 /* version */, sizeof(*pThis), ioapicSaveExec, ioapicLoadExec);
    654610    if (RT_FAILURE(rc))
    655611        return rc;
     
    664620     * Statistics.
    665621     */
    666     PDMDevHlpSTAMRegister(pDevIns, &s->StatMMIOReadGC,     STAMTYPE_COUNTER,  "/Devices/IOAPIC/MMIOReadGC",   STAMUNIT_OCCURENCES, "Number of IOAPIC MMIO reads in GC.");
    667     PDMDevHlpSTAMRegister(pDevIns, &s->StatMMIOReadHC,     STAMTYPE_COUNTER,  "/Devices/IOAPIC/MMIOReadHC",   STAMUNIT_OCCURENCES, "Number of IOAPIC MMIO reads in HC.");
    668     PDMDevHlpSTAMRegister(pDevIns, &s->StatMMIOWriteGC,    STAMTYPE_COUNTER,  "/Devices/IOAPIC/MMIOWriteGC",  STAMUNIT_OCCURENCES, "Number of IOAPIC MMIO writes in GC.");
    669     PDMDevHlpSTAMRegister(pDevIns, &s->StatMMIOWriteHC,    STAMTYPE_COUNTER,  "/Devices/IOAPIC/MMIOWriteHC",  STAMUNIT_OCCURENCES, "Number of IOAPIC MMIO writes in HC.");
    670     PDMDevHlpSTAMRegister(pDevIns, &s->StatSetIrqGC,       STAMTYPE_COUNTER,  "/Devices/IOAPIC/SetIrqGC",     STAMUNIT_OCCURENCES, "Number of IOAPIC SetIrq calls in GC.");
    671     PDMDevHlpSTAMRegister(pDevIns, &s->StatSetIrqHC,       STAMTYPE_COUNTER,  "/Devices/IOAPIC/SetIrqHC",     STAMUNIT_OCCURENCES, "Number of IOAPIC SetIrq calls in HC.");
     622    PDMDevHlpSTAMRegister(pDevIns, &pThis->StatMMIOReadGC,     STAMTYPE_COUNTER,  "/Devices/IOAPIC/MMIOReadGC",   STAMUNIT_OCCURENCES, "Number of IOAPIC MMIO reads in GC.");
     623    PDMDevHlpSTAMRegister(pDevIns, &pThis->StatMMIOReadHC,     STAMTYPE_COUNTER,  "/Devices/IOAPIC/MMIOReadHC",   STAMUNIT_OCCURENCES, "Number of IOAPIC MMIO reads in HC.");
     624    PDMDevHlpSTAMRegister(pDevIns, &pThis->StatMMIOWriteGC,    STAMTYPE_COUNTER,  "/Devices/IOAPIC/MMIOWriteGC",  STAMUNIT_OCCURENCES, "Number of IOAPIC MMIO writes in GC.");
     625    PDMDevHlpSTAMRegister(pDevIns, &pThis->StatMMIOWriteHC,    STAMTYPE_COUNTER,  "/Devices/IOAPIC/MMIOWriteHC",  STAMUNIT_OCCURENCES, "Number of IOAPIC MMIO writes in HC.");
     626    PDMDevHlpSTAMRegister(pDevIns, &pThis->StatSetIrqGC,       STAMTYPE_COUNTER,  "/Devices/IOAPIC/SetIrqGC",     STAMUNIT_OCCURENCES, "Number of IOAPIC SetIrq calls in GC.");
     627    PDMDevHlpSTAMRegister(pDevIns, &pThis->StatSetIrqHC,       STAMTYPE_COUNTER,  "/Devices/IOAPIC/SetIrqHC",     STAMUNIT_OCCURENCES, "Number of IOAPIC SetIrq calls in HC.");
    672628#endif
     629
     630    /*
     631     * Reset the device state.
     632     */
     633    ioapicReset(pDevIns);
    673634
    674635    return VINF_SUCCESS;
Note: See TracChangeset for help on using the changeset viewer.

© 2025 Oracle Support Privacy / Do Not Sell My Info Terms of Use Trademark Policy Automated Access Etiquette