soc/intel/xeon_sp: Add Granite Rapids initial codes
coreboot GNR (Granite Rapids) is a FSP 2.4 based, no-PCH, single IO-APIC Xeon-SP platform. The same set of codes is also used for SRF (Sierra Forest) SoC. This patch initially sets the code set up as a build target with Granite Rapids N-1 FSP (src/vc/intel/fsp/fsp2_0/graniterapids). 1. All register definitions are forked from SPR (Sapphire Rapids) and EBG (Emmitsburg PCH)'s codes are reused. 2. src/soc/intel/xeon_sp/chip_gen6.c is newly added as chip common codes for 6th Gen Xeon-SP SoC (Granite Rapids) and later. Change-Id: I3084e1b5abf25d8d9504bebeaed2a15b916ed56b Signed-off-by: Shuo Liu <shuo.liu@intel.com> Co-authored-by: Gang Chen <gang.c.chen@intel.com> Co-authored-by: Jincheng Li <jincheng.li@intel.com> Reviewed-on: https://review.coreboot.org/c/coreboot/+/81316 Tested-by: build bot (Jenkins) <no-reply@coreboot.org> Reviewed-by: Lean Sheng Tan <sheng.tan@9elements.com>
This commit is contained in:
@@ -5,6 +5,8 @@ ifeq ($(CONFIG_XEON_SP_COMMON_BASE),y)
|
||||
subdirs-$(CONFIG_SOC_INTEL_SKYLAKE_SP) += skx lbg
|
||||
subdirs-$(CONFIG_SOC_INTEL_COOPERLAKE_SP) += cpx lbg
|
||||
subdirs-$(CONFIG_SOC_INTEL_SAPPHIRERAPIDS_SP) += spr ebg
|
||||
## TODO: GNR IBL codes are initially reused from EBG, will update later.
|
||||
subdirs-$(CONFIG_SOC_INTEL_GRANITERAPIDS) += gnr ebg
|
||||
|
||||
bootblock-y += bootblock.c spi.c lpc.c pch.c report_platform.c
|
||||
romstage-y += romstage.c reset.c util.c spi.c pmutil.c memmap.c ddr.c
|
||||
|
98
src/soc/intel/xeon_sp/chip_gen6.c
Normal file
98
src/soc/intel/xeon_sp/chip_gen6.c
Normal file
@@ -0,0 +1,98 @@
|
||||
/* SPDX-License-Identifier: GPL-2.0-or-later */
|
||||
|
||||
#include <acpi/acpigen_pci.h>
|
||||
#include <assert.h>
|
||||
#include <console/console.h>
|
||||
#include <device/pci.h>
|
||||
#include <intelblocks/acpi.h>
|
||||
#include <post.h>
|
||||
#include <soc/acpi.h>
|
||||
#include <soc/chip_common.h>
|
||||
#include <soc/numa.h>
|
||||
#include <soc/soc_util.h>
|
||||
#include <soc/util.h>
|
||||
#include <stdlib.h>
|
||||
|
||||
static const UDS_PCIROOT_RES *domain_to_pciroot_res(const struct device *dev)
|
||||
{
|
||||
assert(dev->path.type == DEVICE_PATH_DOMAIN);
|
||||
const union xeon_domain_path dn = {
|
||||
.domain_path = dev->path.domain.domain
|
||||
};
|
||||
|
||||
const IIO_UDS *hob = get_iio_uds();
|
||||
assert(hob != NULL);
|
||||
|
||||
const UDS_STACK_RES *sr = &hob->PlatformData.IIO_resource[dn.socket].StackRes[dn.stack];
|
||||
for (unsigned int index = 0; index < sr->PciRootBridgeNum; index++) {
|
||||
if (sr->PciRoot[index].BusBase == dev->downstream->secondary)
|
||||
return &sr->PciRoot[index];
|
||||
}
|
||||
|
||||
return NULL;
|
||||
}
|
||||
|
||||
static void iio_pci_domain_read_resources(struct device *dev)
|
||||
{
|
||||
int index = 0;
|
||||
struct resource *res;
|
||||
const UDS_PCIROOT_RES *pr = domain_to_pciroot_res(dev);
|
||||
|
||||
/* Initialize the system-wide I/O space constraints. */
|
||||
if (pr->IoBase <= pr->IoLimit) {
|
||||
res = new_resource(dev, index++);
|
||||
res->base = pr->IoBase;
|
||||
res->limit = pr->IoLimit;
|
||||
res->flags = IORESOURCE_IO | IORESOURCE_ASSIGNED;
|
||||
}
|
||||
|
||||
/* The 0 - 0xfff IO range is not reported by the HOB but still gets decoded */
|
||||
if (is_domain0(dev)) {
|
||||
res = new_resource(dev, index++);
|
||||
res->base = 0;
|
||||
res->limit = 0xfff;
|
||||
res->size = 0x1000;
|
||||
res->flags = IORESOURCE_IO | IORESOURCE_SUBTRACTIVE | IORESOURCE_ASSIGNED;
|
||||
}
|
||||
|
||||
/* Initialize the system-wide memory resources constraints. */
|
||||
if (pr->Mmio32Base <= pr->Mmio32Limit) {
|
||||
res = new_resource(dev, index++);
|
||||
res->base = pr->Mmio32Base;
|
||||
res->limit = pr->Mmio32Limit;
|
||||
res->flags = IORESOURCE_MEM | IORESOURCE_ASSIGNED;
|
||||
}
|
||||
|
||||
/* Initialize the system-wide memory resources constraints. */
|
||||
if (pr->Mmio64Base <= pr->Mmio64Limit) {
|
||||
res = new_resource(dev, index++);
|
||||
res->base = pr->Mmio64Base;
|
||||
res->limit = pr->Mmio64Limit;
|
||||
res->flags = IORESOURCE_MEM | IORESOURCE_ASSIGNED;
|
||||
}
|
||||
}
|
||||
|
||||
static struct device_operations iio_pcie_domain_ops = {
|
||||
.read_resources = iio_pci_domain_read_resources,
|
||||
.set_resources = pci_domain_set_resources,
|
||||
.scan_bus = pci_host_bridge_scan_bus,
|
||||
#if CONFIG(HAVE_ACPI_TABLES)
|
||||
.acpi_name = soc_acpi_name,
|
||||
.write_acpi_tables = northbridge_write_acpi_tables,
|
||||
.acpi_fill_ssdt = pci_domain_fill_ssdt,
|
||||
#endif
|
||||
};
|
||||
|
||||
void create_xeonsp_domains(const union xeon_domain_path dp, struct bus *bus,
|
||||
const xSTACK_RES *sr, const size_t pci_segment_group)
|
||||
{
|
||||
for (unsigned int index = 0; index < sr->PciRootBridgeNum; index++) {
|
||||
const UDS_PCIROOT_RES *pr = &sr->PciRoot[index];
|
||||
create_domain(dp, bus,
|
||||
pr->BusBase,
|
||||
pr->BusLimit,
|
||||
pciroot_res_to_domain_type(sr, pr),
|
||||
&iio_pcie_domain_ops,
|
||||
pci_segment_group);
|
||||
}
|
||||
}
|
130
src/soc/intel/xeon_sp/gnr/Kconfig
Normal file
130
src/soc/intel/xeon_sp/gnr/Kconfig
Normal file
@@ -0,0 +1,130 @@
|
||||
## SPDX-License-Identifier: GPL-2.0-only
|
||||
|
||||
config SOC_INTEL_GRANITERAPIDS
|
||||
bool
|
||||
select MICROCODE_BLOB_NOT_HOOKED_UP
|
||||
select FSP_NVS_DATA_POST_SILICON_INIT
|
||||
select SOC_INTEL_MEM_MAPPED_PM_CONFIGURATION
|
||||
select XEON_SP_COMMON_BASE
|
||||
select PLATFORM_USES_FSP2_4
|
||||
select CACHE_MRC_SETTINGS
|
||||
select CPU_INTEL_TURBO_NOT_PACKAGE_SCOPED
|
||||
select XEON_SP_IBL
|
||||
select DEFAULT_X2APIC_RUNTIME
|
||||
select UDK_202302_BINDING
|
||||
select PLATFORM_USES_FSP2_X86_32
|
||||
select HAVE_IOAT_DOMAINS
|
||||
select FSP_SPEC_VIOLATION_XEON_SP_HEAP_WORKAROUND
|
||||
select VPD
|
||||
help
|
||||
Intel Granite Rapids support
|
||||
|
||||
if SOC_INTEL_GRANITERAPIDS
|
||||
|
||||
config CHIPSET_DEVICETREE
|
||||
string
|
||||
default "soc/intel/xeon_sp/gnr/chipset.cb"
|
||||
|
||||
config FSP_HEADER_PATH
|
||||
string "Location of FSP headers"
|
||||
default "src/vendorcode/intel/fsp/fsp2_0/graniterapids/ap"
|
||||
|
||||
config MAX_CPUS
|
||||
int
|
||||
default 255
|
||||
|
||||
config PCR_BASE_ADDRESS
|
||||
hex
|
||||
default 0xf7000000
|
||||
help
|
||||
This option allows you to select MMIO Base Address of sideband bus.
|
||||
|
||||
config INTEL_PCH_PWRM_BASE_ADDRESS
|
||||
hex
|
||||
default 0xf6800000
|
||||
help
|
||||
PCH PWRM Base address.
|
||||
|
||||
config DCACHE_RAM_BASE
|
||||
hex
|
||||
default 0xfe800000
|
||||
|
||||
config DCACHE_RAM_SIZE
|
||||
hex
|
||||
default 0x1fff00
|
||||
help
|
||||
The size of the cache-as-ram region required during bootblock
|
||||
and/or romstage. FSP-T reserves the upper 0x100 for
|
||||
FspReservedBuffer.
|
||||
|
||||
config DCACHE_BSP_STACK_SIZE
|
||||
hex
|
||||
default 0x60000
|
||||
help
|
||||
The amount of anticipated stack usage in CAR by bootblock and
|
||||
other stages. It needs to include FSP-M stack requirement and
|
||||
CB romstage stack requirement. The integration documentation
|
||||
says this needs to be 256KiB.
|
||||
|
||||
config FSP_M_RC_HEAP_SIZE
|
||||
hex
|
||||
default 0x142000
|
||||
help
|
||||
On xeon_sp/gnr FSP-M has two separate heap managers, one regular
|
||||
whose size and base are controllable via the StackBase and
|
||||
StackSize UPDs and a 'rc' heap manager that is statically
|
||||
allocated at 0xfe800000 (the CAR base) and consumes about 0x142000
|
||||
bytes of memory.
|
||||
|
||||
config HEAP_SIZE
|
||||
hex
|
||||
default 0x80000
|
||||
|
||||
config STACK_SIZE
|
||||
hex
|
||||
default 0x4000
|
||||
|
||||
config FSP_TEMP_RAM_SIZE
|
||||
hex
|
||||
depends on FSP_USES_CB_STACK
|
||||
default 0x58000
|
||||
help
|
||||
The amount of anticipated heap usage in CAR by FSP.
|
||||
Refer to Platform FSP integration guide document to know
|
||||
the exact FSP requirement for Heap setup. The FSP integration
|
||||
documentation says this needs to be at least 128KiB, but practice
|
||||
show this needs to be 256KiB or more.
|
||||
|
||||
config IED_REGION_SIZE
|
||||
hex
|
||||
default 0x400000
|
||||
|
||||
config CPU_BCLK_MHZ
|
||||
int
|
||||
default 100
|
||||
|
||||
# DDR4
|
||||
config DIMM_SPD_SIZE
|
||||
int
|
||||
default 1024
|
||||
|
||||
config MAX_ACPI_TABLE_SIZE_KB
|
||||
int
|
||||
default 224
|
||||
|
||||
config SOC_INTEL_HAS_NCMEM
|
||||
def_bool y
|
||||
|
||||
config SOC_INTEL_MMAPVTD_ONLY_FOR_DPR
|
||||
def_bool y
|
||||
|
||||
config SOC_INTEL_HAS_CXL
|
||||
def_bool n
|
||||
|
||||
config INTEL_SPI_BASE_ADDRESS
|
||||
hex
|
||||
default 0xf6830000
|
||||
help
|
||||
SPI BAR0 Base address.
|
||||
|
||||
endif
|
28
src/soc/intel/xeon_sp/gnr/Makefile.mk
Normal file
28
src/soc/intel/xeon_sp/gnr/Makefile.mk
Normal file
@@ -0,0 +1,28 @@
|
||||
## SPDX-License-Identifier: GPL-2.0-only
|
||||
|
||||
ifeq ($(CONFIG_SOC_INTEL_GRANITERAPIDS),y)
|
||||
|
||||
subdirs-y += ../../../../cpu/intel/turbo
|
||||
subdirs-y += ../../../../cpu/x86/lapic
|
||||
subdirs-y += ../../../../cpu/x86/mtrr
|
||||
subdirs-y += ../../../../cpu/x86/smm
|
||||
subdirs-y += ../../../../cpu/x86/tsc
|
||||
subdirs-y += ../../../../cpu/intel/microcode
|
||||
|
||||
romstage-y += romstage.c
|
||||
romstage-y += soc_util.c
|
||||
romstage-$(CONFIG_DISPLAY_UPD_DATA) += upd_display.c
|
||||
|
||||
ramstage-y += chip.c
|
||||
ramstage-y += cpu.c
|
||||
ramstage-y += soc_util.c
|
||||
ramstage-y += ramstage.c
|
||||
ramstage-y += soc_acpi.c
|
||||
ramstage-y += ../chip_gen6.c
|
||||
|
||||
CPPFLAGS_common += -I$(src)/soc/intel/xeon_sp/gnr/include
|
||||
CPPFLAGS_common += -I$(src)/soc/intel/xeon_sp/gnr
|
||||
|
||||
CFLAGS_common += -fshort-wchar
|
||||
|
||||
endif ## CONFIG_SOC_INTEL_GRANITERAPIDS
|
34
src/soc/intel/xeon_sp/gnr/acpi/gpe.asl
Normal file
34
src/soc/intel/xeon_sp/gnr/acpi/gpe.asl
Normal file
@@ -0,0 +1,34 @@
|
||||
/* SPDX-License-Identifier: GPL-2.0-only */
|
||||
|
||||
#include <soc/iomap.h>
|
||||
|
||||
Scope (\_SB)
|
||||
{
|
||||
Scope (\_GPE)
|
||||
{
|
||||
OperationRegion (PMIO, SystemIO, ACPI_BASE_ADDRESS, 0xFF)
|
||||
Field (PMIO, ByteAcc, NoLock, Preserve) {
|
||||
Offset(0x34), /* 0x34, SMI/SCI STS*/
|
||||
, 9,
|
||||
SGCS, 1, /* SWGPE STS BIT */
|
||||
|
||||
Offset(0x40), /* 0x40, SMI/SCI_EN*/
|
||||
, 17,
|
||||
SGPC, 1, /* SWGPE CTRL BIT */
|
||||
|
||||
Offset(0x6C), /* 0x6C, General Purpose Event 0 Status [127:96] */
|
||||
, 2,
|
||||
SGPS, 1, /* SWGPE STATUS */
|
||||
|
||||
Offset(0x7C), /* 0x7C, General Purpose Event 0 Enable [127:96] */
|
||||
, 2,
|
||||
SGPE, 1 /* SWGPE ENABLE */
|
||||
}
|
||||
Method (_L62, 0, NotSerialized)
|
||||
{
|
||||
DBGO("\\_GPE\\_L62\n")
|
||||
SGPC = 0 // clear SWGPE control
|
||||
SGPS = 1 // clear SWGPE Status
|
||||
}
|
||||
}
|
||||
}
|
59
src/soc/intel/xeon_sp/gnr/chip.c
Normal file
59
src/soc/intel/xeon_sp/gnr/chip.c
Normal file
@@ -0,0 +1,59 @@
|
||||
/* SPDX-License-Identifier: GPL-2.0-only */
|
||||
|
||||
#include <intelblocks/lpc_lib.h>
|
||||
#include <intelblocks/pmclib.h>
|
||||
#include <soc/pm.h>
|
||||
#include <soc/chip_common.h>
|
||||
#include <soc/ramstage.h>
|
||||
|
||||
#include "chip.h"
|
||||
|
||||
struct device_operations hpet_device_ops = {
|
||||
#if CONFIG(HAVE_ACPI_TABLES)
|
||||
.write_acpi_tables = &acpi_write_hpet,
|
||||
#endif
|
||||
};
|
||||
|
||||
struct device_operations cpu_bus_ops = {
|
||||
.init = mp_cpu_bus_init,
|
||||
};
|
||||
|
||||
struct pci_operations soc_pci_ops = {
|
||||
.set_subsystem = pci_dev_set_subsystem,
|
||||
};
|
||||
|
||||
static void chip_enable_dev(struct device *dev)
|
||||
{
|
||||
switch (dev->path.type) {
|
||||
case DEVICE_PATH_GPIO:
|
||||
block_gpio_enable(dev);
|
||||
break;
|
||||
default:
|
||||
break;
|
||||
}
|
||||
}
|
||||
|
||||
static void chip_init(void *data)
|
||||
{
|
||||
printk(BIOS_DEBUG, "coreboot: calling fsp_silicon_init\n");
|
||||
fsp_silicon_init();
|
||||
|
||||
attach_iio_stacks();
|
||||
pch_enable_ioapic();
|
||||
|
||||
pmc_gpe_init();
|
||||
pmc_disable_all_gpe();
|
||||
pmc_write_pm1_control(pmc_read_pm1_control() | SCI_EN);
|
||||
}
|
||||
|
||||
struct chip_operations soc_intel_xeon_sp_gnr_ops = {
|
||||
.name = "Intel GNR",
|
||||
.enable_dev = chip_enable_dev,
|
||||
.init = chip_init,
|
||||
};
|
||||
|
||||
/* UPD parameters to be initialized before SiliconInit */
|
||||
void platform_fsp_silicon_init_params_cb(FSPS_UPD *silupd)
|
||||
{
|
||||
mainboard_silicon_init_params(silupd);
|
||||
}
|
32
src/soc/intel/xeon_sp/gnr/chip.h
Normal file
32
src/soc/intel/xeon_sp/gnr/chip.h
Normal file
@@ -0,0 +1,32 @@
|
||||
/* SPDX-License-Identifier: GPL-2.0-only */
|
||||
|
||||
#ifndef _SOC_CHIP_H_
|
||||
#define _SOC_CHIP_H_
|
||||
|
||||
#include <intelblocks/cfg.h>
|
||||
#include <soc/acpi.h>
|
||||
#include <soc/gpio.h>
|
||||
#include <soc/irq.h>
|
||||
#include <stdint.h>
|
||||
|
||||
struct soc_intel_xeon_sp_gnr_config {
|
||||
/* Common struct containing soc config data required by common code */
|
||||
struct soc_intel_common_config common_soc_config;
|
||||
|
||||
bool vtd_support;
|
||||
uint8_t debug_print_level;
|
||||
uint16_t serial_io_uart_debug_io_base;
|
||||
|
||||
/* Generic IO decode ranges */
|
||||
uint32_t gen1_dec;
|
||||
uint32_t gen2_dec;
|
||||
uint32_t gen3_dec;
|
||||
uint32_t gen4_dec;
|
||||
|
||||
uint32_t tcc_offset;
|
||||
enum acpi_cstate_mode cstate_states;
|
||||
};
|
||||
|
||||
typedef struct soc_intel_xeon_sp_gnr_config config_t;
|
||||
|
||||
#endif
|
21
src/soc/intel/xeon_sp/gnr/chipset.cb
Normal file
21
src/soc/intel/xeon_sp/gnr/chipset.cb
Normal file
@@ -0,0 +1,21 @@
|
||||
## SPDX-License-Identifier: GPL-2.0-or-later
|
||||
|
||||
chip soc/intel/xeon_sp/gnr
|
||||
|
||||
# configure VT-d
|
||||
register "vtd_support" = "1"
|
||||
|
||||
# configure BIOS lockdown
|
||||
register "common_soc_config" = "{
|
||||
.chipset_lockdown = CHIPSET_LOCKDOWN_FSP,
|
||||
}"
|
||||
|
||||
# configure devices
|
||||
device cpu_cluster 0 on ops cpu_bus_ops end
|
||||
|
||||
device domain 0 on
|
||||
device pci 00.0 mandatory end # MMAP/VT-d
|
||||
device gpio 0 alias ibl_gpio_communities on end # GPIO
|
||||
device mmio 0xfed00000 on ops hpet_device_ops end # HPET
|
||||
end
|
||||
end
|
106
src/soc/intel/xeon_sp/gnr/cpu.c
Normal file
106
src/soc/intel/xeon_sp/gnr/cpu.c
Normal file
@@ -0,0 +1,106 @@
|
||||
/* SPDX-License-Identifier: GPL-2.0-only */
|
||||
|
||||
#include <cpu/intel/common/common.h>
|
||||
#include <cpu/intel/microcode.h>
|
||||
#include <cpu/x86/mp.h>
|
||||
#include <cpu/x86/mtrr.h>
|
||||
#include <intelblocks/cpulib.h>
|
||||
#include <intelblocks/mp_init.h>
|
||||
#include <soc/cpu.h>
|
||||
#include <soc/soc_util.h>
|
||||
#include <soc/util.h>
|
||||
|
||||
#include "chip.h"
|
||||
|
||||
static const void *microcode_patch;
|
||||
|
||||
static const config_t *chip_config = NULL;
|
||||
|
||||
bool cpu_soc_is_in_untrusted_mode(void)
|
||||
{
|
||||
// FIXME: not implemented yet
|
||||
return false;
|
||||
}
|
||||
|
||||
void get_microcode_info(const void **microcode, int *parallel)
|
||||
{
|
||||
*microcode = intel_microcode_find();
|
||||
*parallel = 0;
|
||||
}
|
||||
|
||||
static void each_cpu_init(struct device *cpu)
|
||||
{
|
||||
printk(BIOS_SPEW, "%s dev: %s, cpu: %lu, apic_id: 0x%x\n",
|
||||
__func__, dev_path(cpu), cpu_index(), cpu->path.apic.apic_id);
|
||||
|
||||
/* Enable VMX */
|
||||
set_vmx_and_lock();
|
||||
}
|
||||
|
||||
static struct device_operations cpu_dev_ops = {
|
||||
.init = each_cpu_init,
|
||||
};
|
||||
|
||||
static const struct cpu_device_id cpu_table[] = {
|
||||
{ X86_VENDOR_INTEL, CPUID_GRANITERAPIDS, CPUID_ALL_STEPPINGS_MASK },
|
||||
{ X86_VENDOR_INTEL, CPUID_SIERRAFOREST, CPUID_ALL_STEPPINGS_MASK },
|
||||
CPU_TABLE_END
|
||||
};
|
||||
|
||||
static const struct cpu_driver driver __cpu_driver = {
|
||||
.ops = &cpu_dev_ops,
|
||||
.id_table = cpu_table,
|
||||
};
|
||||
|
||||
/*
|
||||
* Do essential initialization tasks before APs can be fired up
|
||||
*/
|
||||
static void pre_mp_init(void)
|
||||
{
|
||||
x86_setup_mtrrs_with_detect();
|
||||
x86_mtrr_check();
|
||||
}
|
||||
|
||||
static int get_thread_count(void)
|
||||
{
|
||||
unsigned int num_phys = 0, num_virts = 0;
|
||||
|
||||
/*
|
||||
* This call calculates the thread count which is corresponding to num_virts
|
||||
* (logical cores), while num_phys is corresponding to physical cores (in SMT
|
||||
* system, one physical core has multiple threads, a.k.a. logical cores).
|
||||
* Hence num_phys is not actually used.
|
||||
*/
|
||||
cpu_read_topology(&num_phys, &num_virts);
|
||||
printk(BIOS_SPEW, "Detected %u cores and %u threads\n", num_phys, num_virts);
|
||||
return num_virts * soc_get_num_cpus();
|
||||
}
|
||||
|
||||
static void post_mp_init(void)
|
||||
{
|
||||
if (CONFIG(HAVE_SMI_HANDLER))
|
||||
global_smi_enable();
|
||||
}
|
||||
|
||||
static const struct mp_ops mp_ops = {
|
||||
.pre_mp_init = pre_mp_init,
|
||||
.get_cpu_count = get_thread_count,
|
||||
.get_microcode_info = get_microcode_info,
|
||||
.post_mp_init = post_mp_init,
|
||||
};
|
||||
|
||||
void mp_init_cpus(struct bus *bus)
|
||||
{
|
||||
/*
|
||||
* chip_config is used in CPU device callback. Other than CPU 0,
|
||||
* rest of the CPU devices do not have chip_info updated.
|
||||
*/
|
||||
chip_config = bus->dev->chip_info;
|
||||
|
||||
microcode_patch = intel_microcode_find();
|
||||
intel_microcode_load_unlocked(microcode_patch);
|
||||
|
||||
enum cb_err ret = mp_init_with_smm(bus, &mp_ops);
|
||||
if (ret != CB_SUCCESS)
|
||||
printk(BIOS_ERR, "MP initialization failure %d.\n", ret);
|
||||
}
|
9
src/soc/intel/xeon_sp/gnr/include/soc/cpu.h
Normal file
9
src/soc/intel/xeon_sp/gnr/include/soc/cpu.h
Normal file
@@ -0,0 +1,9 @@
|
||||
/* SPDX-License-Identifier: GPL-2.0-only */
|
||||
|
||||
#ifndef _SOC_CPU_H
|
||||
#define _SOC_CPU_H
|
||||
|
||||
#define CPUID_GRANITERAPIDS 0xA06D0
|
||||
#define CPUID_SIERRAFOREST 0xA06F0
|
||||
|
||||
#endif
|
201
src/soc/intel/xeon_sp/gnr/include/soc/pci_devs.h
Normal file
201
src/soc/intel/xeon_sp/gnr/include/soc/pci_devs.h
Normal file
@@ -0,0 +1,201 @@
|
||||
/* SPDX-License-Identifier: GPL-2.0-only */
|
||||
|
||||
/* TEMPORARY PLACE HOLDER! DO NOT USE! */
|
||||
/* FORKED FROM src/soc/intel/xeon_sp/spr/include/soc/pci_devs.h */
|
||||
|
||||
#ifndef _SOC_PCI_DEVS_H_
|
||||
#define _SOC_PCI_DEVS_H_
|
||||
|
||||
#include <device/pci_def.h>
|
||||
#include <device/pci_type.h>
|
||||
#include <soc/pch_pci_devs.h>
|
||||
#include <types.h>
|
||||
|
||||
#define _SA_DEVFN(slot) PCI_DEVFN(SA_DEV_SLOT_##slot, 0)
|
||||
|
||||
#if !defined(__SIMPLE_DEVICE__)
|
||||
#include <device/device.h>
|
||||
#define _SA_DEV(slot) pcidev_path_on_root_debug(_SA_DEVFN(slot), __func__)
|
||||
#else
|
||||
#define _SA_DEV(slot) PCI_DEV(0, SA_DEV_SLOT_##slot, 0)
|
||||
#endif
|
||||
|
||||
#define UNCORE_BUS_0 0
|
||||
#define UNCORE_BUS_1 1
|
||||
|
||||
/* UBOX Registers [U(1), D:0, F:1] */
|
||||
#define SMM_FEATURE_CONTROL 0x8c
|
||||
#define SMM_CODE_CHK_EN BIT(2)
|
||||
#define SMM_FEATURE_CONTROL_LOCK BIT(0)
|
||||
#define UBOX_DFX_DEVID 0x3251
|
||||
|
||||
/* CHA registers [B:31, D:29, F:0/F:1]
|
||||
* SAD is the previous xeon_sp register name. Keep defines for shared code.
|
||||
*/
|
||||
#define CHA_DEV 29
|
||||
|
||||
#define SAD_ALL_DEV CHA_DEV
|
||||
#define SAD_ALL_FUNC 0
|
||||
#define SAD_ALL_PAM0123_CSR 0x80
|
||||
#define SAD_ALL_PAM456_CSR 0x84
|
||||
#define SAD_ALL_DEVID 0x344f
|
||||
|
||||
#if !defined(__SIMPLE_DEVICE__)
|
||||
#define _PCU_DEV(bus, func) pcidev_path_on_bus(bus, PCI_DEVFN(PCU_DEV, func))
|
||||
#else
|
||||
#define _PCU_DEV(bus, func) PCI_DEV(bus, PCU_DEV, func)
|
||||
#endif
|
||||
|
||||
/* PCU [B:31, D:30, F:0->F:6] */
|
||||
#define PCU_IIO_STACK UNCORE_BUS_1
|
||||
#define PCU_DEV 30
|
||||
|
||||
#define PCU_CR0_FUN 0
|
||||
#define PCU_CR0_DEVID 0x3258
|
||||
#define PCU_DEV_CR0(bus) _PCU_DEV(bus, PCU_CR0_FUN)
|
||||
#define PCU_CR0_PLATFORM_INFO 0xa8
|
||||
#define PCU_CR0_TURBO_ACTIVATION_RATIO 0xb0
|
||||
#define TURBO_ACTIVATION_RATIO_LOCK BIT(31)
|
||||
#define PCU_CR0_P_STATE_LIMITS 0xd8
|
||||
#define P_STATE_LIMITS_LOCK BIT(31)
|
||||
#define PCU_CR0_PACKAGE_RAPL_LIMIT_LWR 0xe8
|
||||
#define PCU_CR0_PACKAGE_RAPL_LIMIT_UPR (PCU_CR0_PACKAGE_RAPL_LIMIT_LWR + 4)
|
||||
#define PKG_PWR_LIM_LOCK_UPR BIT(31)
|
||||
#define PCU_CR0_PMAX 0xf0
|
||||
#define PMAX_LOCK BIT(31)
|
||||
#define PCU_CR0_VR_CURRENT_CONFIG_CFG 0xf8
|
||||
#define VR_CURRENT_CONFIG_LOCK BIT(31)
|
||||
|
||||
#define PCU_CR1_FUN 1
|
||||
#define PCU_CR1_DEVID 0x3259
|
||||
#define PCU_DEV_CR1(bus) _PCU_DEV(bus, PCU_CR1_FUN)
|
||||
#define PCU_CR1_BIOS_MB_DATA_REG 0x8c
|
||||
|
||||
#define PCU_CR1_BIOS_MB_INTERFACE_REG 0x90
|
||||
#define BIOS_MB_RUN_BUSY_MASK BIT(31)
|
||||
#define BIOS_MB_CMD_MASK 0xff
|
||||
#define BIOS_CMD_READ_PCU_MISC_CFG 0x5
|
||||
#define BIOS_CMD_WRITE_PCU_MISC_CFG 0x6
|
||||
#define BIOS_ERR_INVALID_CMD 0x01
|
||||
|
||||
#define PCU_CR1_BIOS_RESET_CPL_REG 0x94
|
||||
#define RST_CPL1_MASK BIT(1)
|
||||
#define RST_CPL2_MASK BIT(2)
|
||||
#define RST_CPL3_MASK BIT(3)
|
||||
#define RST_CPL4_MASK BIT(4)
|
||||
#define PCODE_INIT_DONE1_MASK BIT(9)
|
||||
#define PCODE_INIT_DONE2_MASK BIT(10)
|
||||
#define PCODE_INIT_DONE3_MASK BIT(11)
|
||||
#define PCODE_INIT_DONE4_MASK BIT(12)
|
||||
|
||||
#define PCU_CR1_DESIRED_CORES_CFG2_REG 0xbc
|
||||
#define PCU_CR1_DESIRED_CORES_CFG2_REG_LOCK_MASK BIT(31)
|
||||
|
||||
#define PCU_CR2_FUN 2
|
||||
#define PCU_CR2_DEVID 0x325a
|
||||
#define PCU_DEV_CR2(bus) _PCU_DEV(bus, PCU_CR2_FUN)
|
||||
#define PCU_CR2_DRAM_POWER_INFO_LWR 0xa8
|
||||
#define PCU_CR2_DRAM_POWER_INFO_UPR (PCU_CR2_DRAM_POWER_INFO_LWR + 4)
|
||||
#define DRAM_POWER_INFO_LOCK_UPR BIT(31)
|
||||
|
||||
#define PCU_CR2_DRAM_PLANE_POWER_LIMIT_LWR 0xf0
|
||||
#define PCU_CR2_DRAM_PLANE_POWER_LIMIT_UPR (PCU_CR2_DRAM_PLANE_POWER_LIMIT_LWR + 4)
|
||||
#define PP_PWR_LIM_LOCK_UPR BIT(31)
|
||||
|
||||
#define PCU_CR3_FUN 3
|
||||
#define PCU_CR3_DEVID 0x325b
|
||||
#define PCU_CR3_CAPID4 0x94
|
||||
#define ERR_SPOOFING_DIS 1
|
||||
#define PCU_DEV_CR3(bus) _PCU_DEV(bus, PCU_CR3_FUN)
|
||||
#define PCU_CR3_CONFIG_TDP_CONTROL 0xd8
|
||||
#define TDP_LOCK BIT(31)
|
||||
#define PCU_CR3_FLEX_RATIO 0xa0
|
||||
#define OC_LOCK BIT(20)
|
||||
|
||||
#define PCU_CR4_FUN 4
|
||||
#define PCU_CR4_DEVID 0x325c
|
||||
#define PCU_VIRAL_CONTROL 0x84
|
||||
#define PCU_FW_ERR_EN (1 << 10)
|
||||
#define PCU_UC_ERR_EN (1 << 9)
|
||||
#define PCU_HW_ERR_EN (1 << 8)
|
||||
#define PCU_EMCA_MODE (1 << 2)
|
||||
|
||||
#define PCU_CR6_FUN 6
|
||||
#define PCU_CR6_DEVID 0x325e
|
||||
#define PCU_DEV_CR6(bus) _PCU_DEV(bus, PCU_CR6_FUN)
|
||||
#define PCU_CR6_PLATFORM_RAPL_LIMIT_CFG_LWR 0xa8
|
||||
#define PCU_CR6_PLATFORM_RAPL_LIMIT_CFG_UPR (PCU_CR6_PLATFORM_RAPL_LIMIT_CFG_LWR + 4)
|
||||
#define PLT_PWR_LIM_LOCK_UPR BIT(31)
|
||||
#define PCU_CR6_PLATFORM_POWER_INFO_CFG_LWR 0xb0
|
||||
#define PCU_CR6_PLATFORM_POWER_INFO_CFG_UPR (PCU_CR6_PLATFORM_POWER_INFO_CFG_LWR + 4)
|
||||
#define PLT_PWR_INFO_LOCK_UPR BIT(31)
|
||||
|
||||
/* Memory Map/VTD Device Functions
|
||||
* These are available in each IIO stack
|
||||
*/
|
||||
#define MMAP_VTD_DEV 0x0
|
||||
#define MMAP_VTD_FUNC 0x0
|
||||
|
||||
#define VTD_TOLM_CSR 0xd0
|
||||
#define VTD_TSEG_BASE_CSR 0xa8
|
||||
#define VTD_TSEG_LIMIT_CSR 0xac
|
||||
#define VTD_EXT_CAP_LOW 0x10
|
||||
#define VTD_MMCFG_BASE_CSR 0x90
|
||||
#define VTD_MMCFG_LIMIT_CSR 0x98
|
||||
#define VTD_TOHM_CSR 0xc8
|
||||
#define VTD_MMIOL_CSR 0xd8
|
||||
#define VTD_NCMEM_BASE_CSR 0xe0
|
||||
#define VTD_NCMEM_LIMIT_CSR 0xe8
|
||||
#define VTD_BAR_CSR 0x180
|
||||
#define VTD_LTDPR 0x290
|
||||
|
||||
#define VMD_DEV_NUM 0x00
|
||||
#define VMD_FUNC_NUM 0x05
|
||||
|
||||
#define MMAP_VTD_CFG_REG_DEVID 0x09a2
|
||||
#define MMAP_VTD_STACK_CFG_REG_DEVID 0x09a2
|
||||
#define VTD_DEV_NUM 0x0
|
||||
#define VTD_FUNC_NUM 0x0
|
||||
|
||||
#if !defined(__SIMPLE_DEVICE__)
|
||||
#define VTD_DEV(bus) pcidev_path_on_bus((bus), PCI_DEVFN(VTD_DEV_NUM, VTD_FUNC_NUM))
|
||||
#else
|
||||
#define VTD_DEV(bus) PCI_DEV((bus), VTD_DEV_NUM, VTD_FUNC_NUM)
|
||||
#endif
|
||||
|
||||
/* Root port Registers */
|
||||
|
||||
/* IEH */
|
||||
#define IEH_EXT_CAP_ID 0x7 /* At 0x160 */
|
||||
#define GSYSEVTCTL 0x104 /* Offset from IEH_EXT_CAP_ID */
|
||||
#define CE_ERR_UNMSK 1
|
||||
#define NON_FATAL_UNMSK (1 << 1)
|
||||
#define FATAL_UNMSK (1 << 2)
|
||||
#define GSYSEVTMAP 0x108 /* Offset from IEH_EXT_CAP_ID */
|
||||
#define CE_SMI 1
|
||||
#define NF_SMI (1 << 2)
|
||||
#define FA_SMI (1 << 4)
|
||||
|
||||
|
||||
#define DMIRCBAR 0x50
|
||||
#define DMI3_DEVID 0x2020
|
||||
#define PCIE_ROOTCTL 0x5c
|
||||
#define ERRINJCON 0x198
|
||||
|
||||
/* IIO DFX Global D7F7 registers */
|
||||
#define IIO_DFX_TSWCTL0 0x30c
|
||||
#define IIO_DFX_LCK_CTL 0x504
|
||||
|
||||
/* XHCI register */
|
||||
#define SYS_BUS_CFG2 0x44
|
||||
|
||||
/* MSM registers */
|
||||
#define MSM_BUS 0xF2
|
||||
#define MSM_DEV 3
|
||||
#define MSM_FUN 0
|
||||
#define MSM_FUN_PMON 1
|
||||
#define CRASHLOG_CTL 0x1B8
|
||||
#define BIOS_CRASHLOG_CTL 0x158
|
||||
#define CRASHLOG_CTL_DIS BIT(2)
|
||||
|
||||
#endif /* _SOC_PCI_DEVS_H_ */
|
64
src/soc/intel/xeon_sp/gnr/include/soc/soc_msr.h
Normal file
64
src/soc/intel/xeon_sp/gnr/include/soc/soc_msr.h
Normal file
@@ -0,0 +1,64 @@
|
||||
/* SPDX-License-Identifier: GPL-2.0-or-later */
|
||||
|
||||
/* TEMPORARY PLACE HOLDER! DO NOT USE! */
|
||||
/* FORMED FROM src/soc/intel/xeon_sp/spr/include/soc/soc_msr.h */
|
||||
|
||||
#ifndef _SOC_MSR_SPR_H_
|
||||
#define _SOC_MSR_SPR_H_
|
||||
|
||||
#define MSR_CPU_BUSNO 0x128
|
||||
#define BUSNO_VALID (1 << 31) /* used as msr.hi */
|
||||
|
||||
/* IA32_ERR_CTRL */
|
||||
#define CMCI_DISABLE (1 << 4)
|
||||
|
||||
/* MSR_PKG_CST_CONFIG_CONTROL */
|
||||
#define PKG_CSTATE_NO_LIMIT (0x8 << PKG_CSTATE_LIMIT_SHIFT)
|
||||
|
||||
/* MSR_POWER_CTL */
|
||||
#define RESERVED1_SHIFT 2
|
||||
#define PWR_PERF_PLTFRM_OVR_SHIFT 18
|
||||
#define PWR_PERF_PLTFRM_OVR (1 << PWR_PERF_PLTFRM_OVR_SHIFT)
|
||||
#define EE_TURBO_DISABLE_SHIFT 19
|
||||
#define EE_TURBO_DISABLE (1 << EE_TURBO_DISABLE_SHIFT)
|
||||
#define RTH_DISABLE_SHIFT 20
|
||||
#define RTH_DISABLE (1 << RTH_DISABLE_SHIFT)
|
||||
#define PROCHOT_OUTPUT_DISABLE_SHIFT 21
|
||||
#define PROCHOT_OUTPUT_DISABLE (1 << PROCHOT_OUTPUT_DISABLE_SHIFT)
|
||||
#define PROCHOT_RESPONSE_SHIFT 22
|
||||
#define PROCHOT_RESPONSE (1 << PROCHOT_RESPONSE_SHIFT)
|
||||
#define PROCHOT_LOCK_SHIFT 23
|
||||
#define PROCHOT_LOCK (1 << PROCHOT_LOCK_SHIFT)
|
||||
#define VR_THERM_ALERT_DISABLE_SHIFT 24
|
||||
#define VR_THERM_ALERT_DISABLE (1 << VR_THERM_ALERT_DISABLE_SHIFT)
|
||||
#define DISABLE_RING_EE_SHIFT 25
|
||||
#define DISABLE_RING_EE (1 << DISABLE_RING_EE_SHIFT)
|
||||
#define RESERVED2_SHIFT 26
|
||||
#define DISABLE_AUTONOMOUS_SHIFT 28
|
||||
#define DISABLE_AUTONOMOUS (1 << DISABLE_AUTONOMOUS_SHIFT)
|
||||
#define RESERVED3_SHIFT 29
|
||||
#define CSTATE_PREWAKE_DISABLE_SHIFT 30
|
||||
#define CSTATE_PREWAKE_DISABLE (1 << CSTATE_PREWAKE_DISABLE_SHIFT)
|
||||
|
||||
/* SPR has banks 0-20 and 29-31 */
|
||||
#define IA32_MC20_CTL2 0x294
|
||||
#define IA32_MC29_CTL2 0x29D
|
||||
#define IA32_MC30_CTL2 0x29E
|
||||
#define IA32_MC31_CTL2 0x29F
|
||||
|
||||
#define MSR_PERRINJ_AT_IP 0x107
|
||||
#define MSR_PERRINJ_AT_IP_ENABLE BIT(31)
|
||||
|
||||
#define MSR_BIOS_DONE 0x151
|
||||
#define XEON_SP_ENABLE_IA_UNTRUSTED BIT(0)
|
||||
|
||||
#define MSR_FLEX_RATIO 0x194
|
||||
#define MSR_FLEX_RATIO_OC_LOCK BIT(20)
|
||||
|
||||
/* B1:D30:F0 offset 0xe8 on previous generations */
|
||||
#define PACKAGE_RAPL_LIMIT 0x610
|
||||
|
||||
#define MSR_DRAM_PLANE_POWER_LIMIT 0x618
|
||||
#define MSR_HI_PP_PWR_LIM_LOCK BIT(31) /* used as msr.hi */
|
||||
|
||||
#endif /* _SOC_MSR_SPR_H_ */
|
31
src/soc/intel/xeon_sp/gnr/include/soc/soc_util.h
Normal file
31
src/soc/intel/xeon_sp/gnr/include/soc/soc_util.h
Normal file
@@ -0,0 +1,31 @@
|
||||
/* SPDX-License-Identifier: GPL-2.0-only */
|
||||
|
||||
#ifndef _SOC_UTIL_H_
|
||||
#define _SOC_UTIL_H_
|
||||
|
||||
#include <device/device.h>
|
||||
#include <device/pci.h>
|
||||
|
||||
#include <fsp/util.h>
|
||||
#include <CxlNodeHob.h>
|
||||
#include <FspAcpiHobs.h>
|
||||
#include <IioUniversalDataHob.h>
|
||||
#include <MemoryMapDataHob.h>
|
||||
|
||||
#define xSTACK_RES UDS_STACK_RES
|
||||
#define xIIO_RESOURCE_INSTANCE UDS_SOCKET_RES
|
||||
|
||||
#define FSP_HOB_IIO_UNIVERSAL_DATA_GUID { \
|
||||
0xa1, 0x96, 0xf3, 0x7f, 0x7d, 0xee, 0x1e, 0x43, \
|
||||
0xba, 0x53, 0x8f, 0xCa, 0x12, 0x7c, 0x44, 0xc0 \
|
||||
}
|
||||
|
||||
const struct SystemMemoryMapHob *get_system_memory_map(void);
|
||||
const struct SystemMemoryMapElement *get_system_memory_map_elment(uint8_t *num);
|
||||
|
||||
const CXL_NODE_SOCKET *get_cxl_node(void);
|
||||
uint8_t get_cxl_node_count(void);
|
||||
|
||||
const char *pciroot_res_to_domain_type(const UDS_STACK_RES *sr, const UDS_PCIROOT_RES *rr);
|
||||
|
||||
#endif /* _SOC_UTIL_H_ */
|
9
src/soc/intel/xeon_sp/gnr/ramstage.c
Normal file
9
src/soc/intel/xeon_sp/gnr/ramstage.c
Normal file
@@ -0,0 +1,9 @@
|
||||
/* SPDX-License-Identifier: GPL-2.0-only */
|
||||
|
||||
#include <fsp/api.h>
|
||||
#include <soc/ramstage.h>
|
||||
|
||||
unsigned int smbios_cpu_get_voltage(void)
|
||||
{
|
||||
return 16; /* Per SMBIOS spec, voltage times 10 */
|
||||
}
|
53
src/soc/intel/xeon_sp/gnr/romstage.c
Normal file
53
src/soc/intel/xeon_sp/gnr/romstage.c
Normal file
@@ -0,0 +1,53 @@
|
||||
/* SPDX-License-Identifier: GPL-2.0-only */
|
||||
|
||||
#include <soc/romstage.h>
|
||||
|
||||
static uint8_t get_mmcfg_base_upd_index(const uint64_t base_addr)
|
||||
{
|
||||
switch (base_addr) {
|
||||
case 1ULL * GiB: // 1G
|
||||
return 0;
|
||||
case 1ULL * GiB + 512ULL * MiB: // 1.5G
|
||||
return 0x1;
|
||||
case 1ULL * GiB + 768ULL * MiB: // 1.75G
|
||||
return 0x2;
|
||||
case 2ULL * GiB: // 2G
|
||||
return 0x3;
|
||||
case 2ULL * GiB + 256ULL * MiB: // 2.25G
|
||||
return 0x4;
|
||||
case 3ULL * GiB: // 3G
|
||||
return 0x5;
|
||||
default: // Auto
|
||||
return 0x6;
|
||||
}
|
||||
}
|
||||
|
||||
static uint8_t get_mmcfg_size_upd_index(const uint64_t size)
|
||||
{
|
||||
switch (size) {
|
||||
case 64ULL * MiB: // 64M
|
||||
return 0;
|
||||
case 128ULL * MiB: // 128M
|
||||
return 0x1;
|
||||
case 256ULL * MiB: // 256M
|
||||
return 0x2;
|
||||
case 512ULL * MiB: // 512M
|
||||
return 0x3;
|
||||
case 1ULL * GiB: // 1G
|
||||
return 0x4;
|
||||
case 2ULL * GiB: // 2G
|
||||
return 0x5;
|
||||
default: // Auto
|
||||
return 0x6;
|
||||
}
|
||||
}
|
||||
|
||||
void platform_fsp_memory_init_params_cb(FSPM_UPD *mupd, uint32_t version)
|
||||
{
|
||||
FSP_M_CONFIG *m_cfg = &mupd->FspmConfig;
|
||||
m_cfg->mmCfgBase = get_mmcfg_base_upd_index(CONFIG_ECAM_MMCONF_BASE_ADDRESS);
|
||||
m_cfg->mmCfgSize = get_mmcfg_size_upd_index(CONFIG_ECAM_MMCONF_LENGTH);
|
||||
|
||||
/* Board level settings */
|
||||
mainboard_memory_init_params(mupd);
|
||||
}
|
41
src/soc/intel/xeon_sp/gnr/soc_acpi.c
Normal file
41
src/soc/intel/xeon_sp/gnr/soc_acpi.c
Normal file
@@ -0,0 +1,41 @@
|
||||
/* SPDX-License-Identifier: GPL-2.0-only */
|
||||
|
||||
#include <assert.h>
|
||||
#include <intelblocks/acpi.h>
|
||||
#include <intelblocks/pcr.h>
|
||||
#include <intelblocks/itss.h>
|
||||
#include <soc/acpi.h>
|
||||
#include <soc/soc_util.h>
|
||||
#include <soc/util.h>
|
||||
#include <soc/itss.h>
|
||||
#include <soc/pcr_ids.h>
|
||||
|
||||
int soc_madt_sci_irq_polarity(int sci)
|
||||
{
|
||||
int reg = sci / IRQS_PER_IPC;
|
||||
int offset = sci % IRQS_PER_IPC;
|
||||
uint32_t val = pcr_read32(PID_ITSS, PCR_ITSS_IPC0_CONF + reg * sizeof(uint32_t));
|
||||
|
||||
return (val & (1 << offset)) ? MP_IRQ_POLARITY_LOW : MP_IRQ_POLARITY_HIGH;
|
||||
}
|
||||
|
||||
uint32_t soc_read_sci_irq_select(void)
|
||||
{
|
||||
const uint16_t pmbase = ACPI_BASE_ADDRESS;
|
||||
return inl(pmbase + PMC_ACPI_CNT);
|
||||
}
|
||||
|
||||
void soc_fill_fadt(acpi_fadt_t *fadt)
|
||||
{
|
||||
const uint16_t pmbase = ACPI_BASE_ADDRESS;
|
||||
|
||||
fadt->pm_tmr_blk = pmbase + PM1_TMR;
|
||||
fadt->pm_tmr_len = 4;
|
||||
fadt->flags &= ~(ACPI_FADT_SEALED_CASE | ACPI_FADT_S4_RTC_WAKE);
|
||||
fadt->preferred_pm_profile = PM_ENTERPRISE_SERVER;
|
||||
}
|
||||
|
||||
void soc_power_states_generation(int core, int cores_per_package)
|
||||
{
|
||||
generate_p_state_entries(core, cores_per_package);
|
||||
}
|
150
src/soc/intel/xeon_sp/gnr/soc_util.c
Normal file
150
src/soc/intel/xeon_sp/gnr/soc_util.c
Normal file
@@ -0,0 +1,150 @@
|
||||
/* SPDX-License-Identifier: GPL-2.0-only */
|
||||
|
||||
#include <assert.h>
|
||||
#include <device/device.h>
|
||||
#include <device/pci.h>
|
||||
#include <fsp/util.h>
|
||||
#include <soc/util.h>
|
||||
#include <soc/acpi.h>
|
||||
#include <soc/chip_common.h>
|
||||
#include <soc/cpu.h>
|
||||
#include <soc/pci_devs.h>
|
||||
#include <soc/soc_util.h>
|
||||
#include <stdlib.h>
|
||||
#include <string.h>
|
||||
#include <MemoryMapDataHob.h>
|
||||
|
||||
const char *pciroot_res_to_domain_type(const UDS_STACK_RES *sr, const UDS_PCIROOT_RES *pr)
|
||||
{
|
||||
int index = 0;
|
||||
int instance = -1;
|
||||
|
||||
for (; index < sr->PciRootBridgeNum; index++) {
|
||||
if (sr->PciRoot[index].UidType == pr->UidType)
|
||||
instance++;
|
||||
if (sr->PciRoot[index].BusBase == pr->BusBase)
|
||||
break;
|
||||
}
|
||||
|
||||
if (index == sr->PciRootBridgeNum)
|
||||
return NULL;
|
||||
|
||||
switch (pr->UidType) {
|
||||
case PC_UID:
|
||||
return DOMAIN_TYPE_PCIE;
|
||||
case DINO_UID:
|
||||
return DOMAIN_TYPE_DINO;
|
||||
case CPM0_UID:
|
||||
return DOMAIN_TYPE_CPM0;
|
||||
case HQM0_UID:
|
||||
return DOMAIN_TYPE_HQM0;
|
||||
case UB_UID:
|
||||
return (instance == 0) ? DOMAIN_TYPE_UBX0 : DOMAIN_TYPE_UBX1;
|
||||
default:
|
||||
return NULL;
|
||||
}
|
||||
}
|
||||
|
||||
static bool is_domain_type_supported_on_stack(const xSTACK_RES *sr, const char *dt)
|
||||
{
|
||||
for (unsigned int index = 0; index < sr->PciRootBridgeNum; index++)
|
||||
if (!strcmp(dt, pciroot_res_to_domain_type(sr, &sr->PciRoot[index])))
|
||||
return true;
|
||||
|
||||
return false;
|
||||
}
|
||||
|
||||
bool is_pcie_iio_stack_res(const xSTACK_RES *res)
|
||||
{
|
||||
return is_domain_type_supported_on_stack(res, DOMAIN_TYPE_PCIE);
|
||||
}
|
||||
|
||||
bool is_ioat_iio_stack_res(const xSTACK_RES *res)
|
||||
{
|
||||
return (is_domain_type_supported_on_stack(res, DOMAIN_TYPE_DINO) ||
|
||||
is_domain_type_supported_on_stack(res, DOMAIN_TYPE_CPM0) ||
|
||||
is_domain_type_supported_on_stack(res, DOMAIN_TYPE_HQM0));
|
||||
|
||||
}
|
||||
|
||||
bool is_ubox_stack_res(const xSTACK_RES *res)
|
||||
{
|
||||
return (is_domain_type_supported_on_stack(res, DOMAIN_TYPE_UBX0) ||
|
||||
is_domain_type_supported_on_stack(res, DOMAIN_TYPE_UBX1));
|
||||
}
|
||||
|
||||
bool is_iio_cxl_stack_res(const xSTACK_RES *res)
|
||||
{
|
||||
return false;
|
||||
}
|
||||
|
||||
const struct SystemMemoryMapHob *get_system_memory_map(void)
|
||||
{
|
||||
size_t hob_size;
|
||||
const EFI_GUID mem_hob_guid = MEMORY_MAP_HOB_GUID;
|
||||
const struct SystemMemoryMapHob **memmap_addr;
|
||||
|
||||
memmap_addr = (const struct SystemMemoryMapHob **)
|
||||
fsp_find_extension_hob_by_guid((uint8_t *)&mem_hob_guid, &hob_size);
|
||||
/* hob_size is the size of the 8-byte address not the hob data */
|
||||
assert(memmap_addr != NULL && hob_size != 0);
|
||||
/* assert the pointer to the hob is not NULL */
|
||||
assert(*memmap_addr != NULL);
|
||||
|
||||
return *memmap_addr;
|
||||
}
|
||||
|
||||
const struct SystemMemoryMapElement *get_system_memory_map_elment(uint8_t *num)
|
||||
{
|
||||
const struct SystemMemoryMapHob *hob = get_system_memory_map();
|
||||
if (!hob)
|
||||
return NULL;
|
||||
|
||||
*num = hob->numberEntries;
|
||||
return hob->Element;
|
||||
}
|
||||
|
||||
const CXL_NODE_SOCKET *get_cxl_node(void)
|
||||
{
|
||||
size_t hob_size;
|
||||
static const CXL_NODE_SOCKET *hob;
|
||||
const EFI_GUID fsp_hob_cxl_node_socket_guid = CXL_NODE_HOB_GUID;
|
||||
|
||||
if (hob != NULL)
|
||||
return hob;
|
||||
|
||||
hob = fsp_find_extension_hob_by_guid((uint8_t *)&fsp_hob_cxl_node_socket_guid, &hob_size);
|
||||
if (hob == NULL || hob_size == 0) {
|
||||
printk(BIOS_DEBUG, "CXL_NODE_HOB_GUID not found: CXL may not be installed\n");
|
||||
return NULL;
|
||||
}
|
||||
return hob;
|
||||
}
|
||||
|
||||
uint8_t get_cxl_node_count(void)
|
||||
{
|
||||
const CXL_NODE_SOCKET *hob = get_cxl_node();
|
||||
uint8_t count = 0;
|
||||
|
||||
if (hob == NULL)
|
||||
return 0;
|
||||
for (unsigned int skt_id = 0 ; skt_id < MAX_SOCKET; skt_id++)
|
||||
count += hob[skt_id].CxlNodeCount;
|
||||
|
||||
return count;
|
||||
}
|
||||
|
||||
bool is_memtype_reserved(uint16_t mem_type)
|
||||
{
|
||||
return false;
|
||||
}
|
||||
|
||||
bool is_memtype_non_volatile(uint16_t mem_type)
|
||||
{
|
||||
return false;
|
||||
}
|
||||
|
||||
bool is_memtype_processor_attached(uint16_t mem_type)
|
||||
{
|
||||
return true;
|
||||
}
|
Reference in New Issue
Block a user