Add constants for fast path resume copying
[coreboot.git] / src / vendorcode / amd / agesa / f14 / cpcar.inc
1 ;*****************************************************************************
2 ; AMD Generic Encapsulated Software Architecture
3 ;
4 ; $Workfile:: cpcar.inc
5 ;
6 ; Description: CPCAR.INC - AGESA cache-as-RAM setup Include File
7 ;
8 ;*****************************************************************************
9
10 ;  Copyright (c) 2011, Advanced Micro Devices, Inc.
11 ;  All rights reserved.
12 ;  
13 ;  Redistribution and use in source and binary forms, with or without
14 ;  modification, are permitted provided that the following conditions are met:
15 ;      * Redistributions of source code must retain the above copyright
16 ;        notice, this list of conditions and the following disclaimer.
17 ;      * Redistributions in binary form must reproduce the above copyright
18 ;        notice, this list of conditions and the following disclaimer in the
19 ;        documentation and/or other materials provided with the distribution.
20 ;      * Neither the name of Advanced Micro Devices, Inc. nor the names of 
21 ;        its contributors may be used to endorse or promote products derived 
22 ;        from this software without specific prior written permission.
23 ;  
24 ;  THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND
25 ;  ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
26 ;  WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
27 ;  DISCLAIMED. IN NO EVENT SHALL ADVANCED MICRO DEVICES, INC. BE LIABLE FOR ANY
28 ;  DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES
29 ;  (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
30 ;  LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND
31 ;  ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
32 ;  (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS
33 ;  SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
34 ;  
35 ;*****************************************************************************
36
37 BSP_STACK_BASE_ADDR     EQU 30000h      ; Base address for primary cores stack
38 BSP_STACK_SIZE          EQU 10000h      ; 64KB for BSP core
39 CORE0_STACK_BASE_ADDR   EQU 80000h      ; Base address for primary cores stack
40 CORE0_STACK_SIZE        EQU 4000h       ; 16KB for primary cores
41 CORE1_STACK_BASE_ADDR   EQU 40000h      ; Base address for AP cores
42 CORE1_STACK_SIZE        EQU 1000h       ; 4KB for each AP cores
43
44 APIC_BASE_ADDRESS       EQU 0000001Bh
45     APIC_BSC                EQU 8       ; Boot Strap Core
46
47 AMD_MTRR_VARIABLE_BASE0 EQU 0200h
48 AMD_MTRR_VARIABLE_BASE6 EQU 020Ch
49 AMD_MTRR_FIX64k_00000   EQU 0250h
50 AMD_MTRR_FIX16k_80000   EQU 0258h
51 AMD_MTRR_FIX16k_A0000   EQU 0259h
52 AMD_MTRR_FIX4k_C0000    EQU 0268h
53 AMD_MTRR_FIX4k_C8000    EQU 0269h
54 AMD_MTRR_FIX4k_D0000    EQU 026Ah
55 AMD_MTRR_FIX4k_D8000    EQU 026Bh
56 AMD_MTRR_FIX4k_E0000    EQU 026Ch
57 AMD_MTRR_FIX4k_E8000    EQU 026Dh
58 AMD_MTRR_FIX4k_F0000    EQU 026Eh
59 AMD_MTRR_FIX4k_F8000    EQU 026Fh
60
61 AMD_MTRR_DEFTYPE        EQU 02FFh
62     WB_DRAM_TYPE            EQU 1Eh     ; MemType - memory type
63     MTRR_DEF_TYPE_EN        EQU 11      ; MtrrDefTypeEn - variable and fixed MTRRs default enabled
64     MTRR_DEF_TYPE_FIX_EN    EQU 10      ; MtrrDefTypeEn - fixed MTRRs default enabled
65
66 HWCR                    EQU 0C0010015h  ; Hardware Configuration
67     INVD_WBINVD             EQU 4       ;   INVD to WBINVD conversion
68
69 IORR_BASE               EQU 0C0010016h  ; IO Range Regusters Base/Mask, 2 pairs
70                                         ;   uses 16h - 19h
71 TOP_MEM                 EQU 0C001001Ah  ; Top of Memory
72 TOP_MEM2                EQU 0C001001Dh  ; Top of Memory2
73
74 LS_CFG                  EQU 0C0011020h  ; Load-Store Configuration
75     DIS_SS                  EQU 28      ;   Family 10h,12h,15h:Disable Streaming Store functionality
76     DIS_STREAM_ST           EQU 28      ;   Family 14h:DisStreamSt - Disable Streaming Store functionality
77
78 IC_CFG                  EQU 0C0011021h  ; Instruction Cache Config Register
79     IC_DIS_SPEC_TLB_RLD     EQU 9       ;   Disable speculative TLB reloads
80     DIS_IND                 EQU 14      ;   Family 10-14h:Disable Indirect Branch Predictor
81     DIS_I_CACHE             EQU 14      ;   Family 15h:DisICache - Disable Indirect Branch Predictor
82
83 DC_CFG                  EQU 0C0011022h  ; Data Cache Configuration
84     DC_DIS_SPEC_TLB_RLD     EQU 4       ;   Disable speculative TLB reloads
85     DIS_CLR_WBTOL2_SMC_HIT  EQU 8       ;   self modifying code check buffer bit
86     DIS_HW_PF               EQU 13      ;   Hardware prefetches bit
87
88 DE_CFG                  EQU 0C0011029h  ; Decode Configuration
89     CL_FLUSH_SERIALIZE      EQU 23      ;   Family 12h,15h: CL Flush Serialization
90
91 BU_CFG2                 EQU 0C001102Ah  ; Family 10h: Bus Unit Configuration 2
92 CU_CFG2                 EQU 0C001102Ah  ; Family 15h: Combined Unit Configuration 2
93     F10_CL_LINES_TO_NB_DIS  EQU 15      ;   ClLinesToNbDis - allows WP code to be cached in L2
94     IC_DIS_SPEC_TLB_WR      EQU 35      ;   IcDisSpecTlbWr - ITLB speculative writes
95
96 CU_CFG3                 EQU 0C001102Bh  ; Combined Unit Configuration 3
97     COMBINE_CR0_CD          EQU 49      ;   Combine CR0.CD for both cores of a compute unit
98
99
100 CR0_PE                  EQU 1           ; Protection Enable
101 CR0_NW                  EQU 29          ; Not Write-through
102 CR0_CD                  EQU 30          ; Cache Disable
103 CR0_PG                  EQU 31          ; Paging Enable
104
105 ; CPUID Functions
106
107 CPUID_MODEL             EQU 1
108 AMD_CPUID_FMF           EQU 80000001h   ; Family Model Features information
109 AMD_CPUID_APIC          EQU 80000008h   ; Long Mode and APIC info., core count
110
111 NB_CFG                  EQU 0C001001Fh  ; Northbridge Configuration Register
112     INIT_APIC_ID_CPU_ID_LO   EQU 54     ;   InitApicIdCpuIdLo - is core# in high or low half of APIC ID?
113
114 MTRR_SYS_CFG            EQU 0C0010010h  ; System Configuration Register
115   CHX_TO_DIRTY_DIS          EQU 16      ;   ChxToDirtyDis    Change to dirty disable
116   SYS_UC_LOCK_EN            EQU 17      ;   SysUcLockEn      System lock command enable
117   MTRR_FIX_DRAM_EN          EQU 18      ;   MtrrFixDramEn    MTRR fixed RdDram and WrDram attributes enable
118   MTRR_FIX_DRAM_MOD_EN      EQU 19      ;   MtrrFixDramModEn MTRR fixed RdDram and WrDram modification enable
119   MTRR_VAR_DRAM_EN          EQU 20      ;   MtrrVarDramEn    MTRR variable DRAM enable
120   MTRR_TOM2_EN              EQU 21      ;   MtrrTom2En       MTRR top of memory 2 enable
121
122 PERF_CONTROL3           EQU 0C0010003h  ; Performance event control three
123     PERF_CONTROL3_RESERVE_L EQU 00200000h ; Preserve the reserved bits
124     PERF_CONTROL3_RESERVE_H EQU 0FCF0h  ; Preserve the reserved bits
125     CONFIG_EVENT_L          EQU 0F0E2h  ; All cores with level detection
126     CONFIG_EVENT_H          EQU 4       ; Increment count by number of event
127                                         ; occured in clock cycle
128     EVENT_ENABLE            EQU 22      ; Enable the event
129 PERF_COUNTER3           EQU 0C0010007h  ; Performance event counter three
130
131 ; Local use flags, in upper most byte if ESI
132 FLAG_UNKNOWN_FAMILY     EQU 24          ; Signals that the family# of the installed processor is not recognized
133 FLAG_STACK_REENTRY      EQU 25          ; Signals that the environment has made a re-entry (2nd) call to set up the stack
134 FLAG_IS_PRIMARY         EQU 26          ; Signals that this core is the primary within the comoute unit
135
136 ; AGESA_STATUS values
137 IFNDEF AGESA_SUCCESS
138        AGESA_SUCCESS  EQU 0
139 ENDIF
140 IFNDEF AGESA_WARNING
141        AGESA_WARNING  EQU 4
142 ENDIF
143 IFNDEF AGESA_FATAL
144        AGESA_FATAL    EQU 7
145 ENDIF
146 ;;***************************************************************************
147 ;;
148 ;;                      CPU MACROS - PUBLIC
149 ;;
150 ;;***************************************************************************
151 _WRMSR macro
152   db  0Fh, 30h
153   endm
154
155 _RDMSR macro
156   db  0Fh, 32h
157   endm
158
159 AMD_CPUID MACRO arg0
160   IFB <arg0>
161     mov   eax, 1
162     db    0Fh, 0A2h                     ; Execute instruction
163     bswap eax
164     xchg  al, ah                        ; Ext model in al now
165     rol   eax, 8                        ; Ext model in ah, model in al
166     and   ax, 0FFCFh                    ; Keep 23:16, 7:6, 3:0
167   ELSE
168     mov   eax, arg0
169     db    0Fh, 0A2h
170   ENDIF
171 ENDM
172
173
174 ;---------------------------------------------------
175 ;
176 ; AMD_ENABLE_STACK_FAMILY_HOOK Macro - Stackless
177 ;
178 ;   Set any family specific controls needed to enable the use of
179 ;   cache as general storage before main memory is available.
180 ;
181 ; Inputs:
182 ;       none
183 ; Outputs:
184 ;       none
185 ;---------------------------------------------------
186 AMD_ENABLE_STACK_FAMILY_HOOK MACRO
187
188     AMD_ENABLE_STACK_FAMILY_HOOK_F10
189     AMD_ENABLE_STACK_FAMILY_HOOK_F12
190     AMD_ENABLE_STACK_FAMILY_HOOK_F14
191     AMD_ENABLE_STACK_FAMILY_HOOK_F15
192
193 ENDM
194
195 ;----------------------------------------------
196 ;
197 ; AMD_DISABLE_STACK_FAMILY_HOOK Macro - Stackless
198 ;
199 ;   Return any family specific controls to their 'standard'
200 ;   settings for using cache with main memory.
201 ;
202 ; Inputs:
203 ;       none
204 ; Outputs:
205 ;       none
206 ;----------------------------------------------
207 AMD_DISABLE_STACK_FAMILY_HOOK MACRO
208
209     AMD_DISABLE_STACK_FAMILY_HOOK_F10
210     AMD_DISABLE_STACK_FAMILY_HOOK_F12
211     AMD_DISABLE_STACK_FAMILY_HOOK_F14
212     AMD_DISABLE_STACK_FAMILY_HOOK_F15
213
214 ENDM
215
216 ;---------------------------------------------------
217 ;
218 ; GET_NODE_ID_CORE_ID Macro - Stackless
219 ;
220 ;   Read family specific values to determine the node and core
221 ;   numbers for the core executing this code.
222 ;
223 ; Inputs:
224 ;     none
225 ; Outputs:
226 ;     SI[7:0] = Core# (0..N, relative to node)
227 ;     SI[15:8]= Node# (0..N)
228 ;     SI[23:16]= reserved
229 ;     SI[24]=   flag: 1=Family Unrecognized
230 ;     SI[25]=   flag: 1=Interface re-entry call
231 ;     SI[26]=   flag: 1=Core is primary of compute unit
232 ;     SI[31:27]= reserved, =0
233 ;---------------------------------------------------
234 GET_NODE_ID_CORE_ID MACRO
235
236     mov     si, -1
237     GET_NODE_ID_CORE_ID_F10
238     GET_NODE_ID_CORE_ID_F12
239     GET_NODE_ID_CORE_ID_F14
240     GET_NODE_ID_CORE_ID_F15
241       ;
242       ; Check for unrecognized Family
243       ;
244     .if (si == -1)                      ; Has family (node/core) been discovered?
245         mov     esi, ( (1 SHL FLAG_UNKNOWN_FAMILY)+(1 SHL FLAG_IS_PRIMARY) ) ; No, Set error code, Only let BSP continue
246         mov     ecx, APIC_BASE_ADDRESS  ; MSR:0000_001B
247         _RDMSR
248         bt      eax, APIC_BSC           ;   Is this the BSC?
249         .if (!carry?)
250             ; No, this is an AP
251             hlt                         ;       Kill APs
252         .endif
253     .endif
254 ENDM
255
256
257
258
259 ;;***************************************************************************
260 ;;                      Family 10h MACROS
261 ;;***************************************************************************
262 ;---------------------------------------------------
263 ;
264 ; AMD_ENABLE_STACK_FAMILY_HOOK_F10 Macro - Stackless
265 ;
266 ;   Set any family specific controls needed to enable the use of
267 ;   cache as general storage before main memory is available.
268 ;
269 ; Inputs:
270 ;       ESI - node#, core#, flags from GET_NODE_ID_CORE_ID
271 ; Outputs:
272 ;       none
273 ;
274 ; Family 10h requirements (BKDG section 2.3.3):
275 ;   * Paging disabled
276 ;   * MSRC001_0015[INVDWBINVD]=0
277 ;   * MSRC001_1021[DIS_IND]=1
278 ;   * MSRC001_1021[DIS_SPEC_TLB_RLD]=1
279 ;   * MSRC001_1022[DIS_SPEC_TLB_RLD]=1
280 ;   * MSRC001_1022[DIS_CLR_WBTOL2_SMC_HIT]=1
281 ;   * MSRC001_1022[DIS_HW_PF]=1
282 ;   * MSRC001_102A[IcDisSpecTlbWr]=1
283 ;   * MSRC001_102A[ClLinesToNbDis]=1
284 ;   * No INVD or WBINVD, no exceptions, page faults or interrupts
285 ;---------------------------------------------------
286 AMD_ENABLE_STACK_FAMILY_HOOK_F10 MACRO
287     local   fam10_enable_stack_hook_exit
288
289     AMD_CPUID   CPUID_MODEL
290     shr     eax, 20                     ; AL = cpu extended family
291     cmp     al, 01h                     ; Is this family 10h?
292     jnz     fam10_enable_stack_hook_exit ; Br if no
293
294     mov     ecx, DC_CFG                 ; MSR:C001_1022
295     _RDMSR
296     bts     eax, DC_DIS_SPEC_TLB_RLD    ; Turn on Disable speculative DTLB reloads bit
297     bts     eax, DIS_CLR_WBTOL2_SMC_HIT ; Turn on Disable the self modifying code check buffer bit
298     bts     eax, DIS_HW_PF              ; Turn on Disable hardware prefetches bit
299     _WRMSR
300
301     dec     cx                          ; MSR:C001_1021
302     _RDMSR
303     bts     eax, IC_DIS_SPEC_TLB_RLD    ; Turn on Disable speculative TLB reloads bit
304     bts     eax, DIS_IND                ; Turn on Disable indirect branch predictor
305     _WRMSR
306
307     mov     ecx, BU_CFG2                ; MSR C001_102A
308     _RDMSR
309     bts     eax, F10_CL_LINES_TO_NB_DIS  ; Allow BIOS ROM to be cached in the IC
310     bts     edx, (IC_DIS_SPEC_TLB_WR-32) ;Disable speculative writes to the ITLB
311     _WRMSR
312
313     mov     ecx, HWCR                   ; MSR C001_0015
314     _RDMSR
315
316     bt      esi, FLAG_STACK_REENTRY     ; Check if stack has already been set
317     .if (!carry?)
318         btr     eax, INVD_WBINVD        ; disable INVD -> WBINVD conversion
319         _WRMSR
320     .endif
321
322     mov eax, esi                        ; load core#
323     .if (al == 0)                       ; If (BSP)
324         mov     ecx, PERF_COUNTER3      ;   Select performance counter three
325                                         ;   to count number of CAR evictions
326         xor     eax, eax                ;   Initialize the lower part of the counter to zero
327         xor     edx, edx                ;   Initializa the upper part of the counter to zero
328         _WRMSR                          ;   Save it
329         mov     ecx, PERF_CONTROL3      ;   Select the event control three
330         _RDMSR                          ;   Get the current setting
331         and     eax, PERF_CONTROL3_RESERVE_L  ; Preserve the reserved bits
332         or      eax, CONFIG_EVENT_L     ;   Set the lower part of event register to
333                                         ;   select CAR Corruption occurred by any cores
334         and     dx, PERF_CONTROL3_RESERVE_H  ; Preserve the reserved bits
335         or      dx, CONFIG_EVENT_H      ;   Set the upper part of event register
336         _WRMSR                          ;   Save it
337         bts     eax, EVENT_ENABLE       ;   Enable it
338         _WRMSR                          ;   Save it
339     .endif                              ; endif
340
341 fam10_enable_stack_hook_exit:
342 ENDM
343
344 ;----------------------------------------------
345 ;
346 ; AMD_DISABLE_STACK_FAMILY_HOOK_F10 Macro - Stackless
347 ;
348 ;   Return any family specific controls to their 'standard'
349 ;   settings for using cache with main memory.
350 ;
351 ; Inputs:
352 ;       ESI - [31:24] flags; [15,8]= Node#; [7,0]= core#
353 ; Outputs:
354 ;       none
355 ;
356 ; Family 10h requirements:
357 ;   * INVD or WBINVD
358 ;   * MSRC001_0015[INVD_WBINVD]=1
359 ;   * MSRC001_1021[DIS_IND]=0
360 ;   * MSRC001_1021[DIS_SPEC_TLB_RLD]=0
361 ;   * MSRC001_1022[DIS_SPEC_TLB_RLD]=0
362 ;   * MSRC001_1022[DIS_CLR_WBTOL2_SMC_HIT]=0
363 ;   * MSRC001_1022[DIS_HW_PF]=0
364 ;   * MSRC001_102A[IcDisSpecTlbWr]=0
365 ;   * MSRC001_102A[ClLinesToNbDis]=0
366 ;----------------------------------------------
367 AMD_DISABLE_STACK_FAMILY_HOOK_F10 MACRO
368     local   fam10_disable_stack_hook_exit
369
370     AMD_CPUID   CPUID_MODEL
371     shr     eax, 20                     ; AL = cpu extended family
372     cmp     al, 01h                     ; Is this family 10h?
373     jnz     fam10_disable_stack_hook_exit ; Br if no
374
375     mov     ecx, DC_CFG                 ; MSR:C001_1022
376     _RDMSR
377     btr     eax, DC_DIS_SPEC_TLB_RLD    ; Enable speculative TLB reloads
378     btr     eax, DIS_CLR_WBTOL2_SMC_HIT ; Allow self modifying code check buffer
379     btr     eax, DIS_HW_PF              ; Allow hardware prefetches
380     _WRMSR
381
382     dec     cx                          ; MSR:C001_1021
383     _RDMSR
384     btr     eax, DIS_IND                ; Turn on indirect branch predictor
385     btr     eax, IC_DIS_SPEC_TLB_RLD    ; Turn on speculative TLB reloads
386     _WRMSR
387
388     mov     ecx, BU_CFG2                ; MSR:C001_102A
389     _RDMSR
390     btr     eax, F10_CL_LINES_TO_NB_DIS  ; Return L3 to normal mode
391     btr     edx, (IC_DIS_SPEC_TLB_WR-32) ;Re-enable speculative writes to the ITLB
392     _WRMSR
393
394     ;--------------------------------------------------------------------------
395     ; Begin critical sequence in which EAX, BX, ECX, and EDX must be preserved.
396     ;--------------------------------------------------------------------------
397     mov     ecx, HWCR                   ; MSR:0000_0015
398     _RDMSR
399     mov     bx, ax                      ; Save INVD -> WBINVD bit
400     btr     eax, INVD_WBINVD            ; Disable INVD -> WBINVD conversion for the invd instruction.
401     _WRMSR
402     invd                                ; Clear the cache tag RAMs
403     mov     ax, bx                      ; Restore INVD -> WBINVD bit
404     _WRMSR
405
406     ;--------------------------------------------------------------------------
407     ; End critical sequence in which EAX, BX, ECX, and EDX must be preserved.
408     ;--------------------------------------------------------------------------
409
410     mov     ecx, PERF_CONTROL3          ; Select the event control three
411     _RDMSR                              ; Retrieve the current value
412     btc     eax, EVENT_ENABLE           ; Is event enable, complement it as well
413     jnc     fam10_disable_stack_hook_exit ; No
414     cmp     ax, CONFIG_EVENT_L          ; Is the lower part of event set to capture the CAR Corruption
415     jne     fam10_disable_stack_hook_exit ; No
416     cmp     dl,  CONFIG_EVENT_H         ; Is the upper part of event set to capture the CAR Corruption
417     jne     fam10_disable_stack_hook_exit ; No
418     _WRMSR                              ; Disable the event
419
420 fam10_disable_stack_hook_exit:
421 ENDM
422
423 ;---------------------------------------------------
424 ;
425 ; GET_NODE_ID_CORE_ID_F10 Macro - Stackless
426 ;
427 ;   Read family specific values to determine the node and core
428 ;   numbers for the core executing this code.
429 ;
430 ; Inputs:
431 ;     none
432 ; Outputs:
433 ;     SI = core#, node# & flags (see GET_NODE_ID_CORE_ID macro above)
434 ;---------------------------------------------------
435 GET_NODE_ID_CORE_ID_F10 MACRO
436
437     local   node_core_f10_exit
438
439     cmp     si, -1                      ; Has node/core already been discovered?
440     jnz     node_core_f10_exit          ; Br if yes
441
442     AMD_CPUID   CPUID_MODEL
443     shr     eax, 20                     ; AL = cpu extended family
444     cmp     al, 01h                     ; Is this family 10h?
445     jnz     node_core_f10_exit          ; Br if no
446
447     xor     esi, esi                    ; Assume BSC, clear flags
448     mov     ecx, APIC_BASE_ADDRESS      ; MSR:0000_001B
449     _RDMSR
450     bt      eax, APIC_BSC               ; Is this the BSC?
451     .if (carry?)
452         ; This is the BSP.
453         ; Enable routing tables on BSP (just in case the HT init code has not yet enabled them)
454         mov     eax, 8000C06Ch          ;   PCI address for D18F0x6C Link Initialization Control Register
455         mov     dx, 0CF8h
456         out     dx, eax
457         add     dx, 4
458         in      eax, dx
459         btr     eax, 0                  ;   Set LinkInitializationControl[RouteTblDis] = 0
460         out     dx, eax
461     .else
462         ; This is an AP. Routing tables have been enabled by the HT Init process.
463         ; Also, the MailBox register was set by the BSP during early init
464         ;   The Mailbox register content is formatted as follows:
465         ;         UINT32 Node:4;        // The node id of Core's node.
466         ;         UINT32 Socket:4;      // The socket of this Core's node.
467         ;         UINT32 Module:2;      // The internal module number for Core's node.
468         ;         UINT32 ModuleType:2;  // Single Module = 0, Multi-module = 1.
469         ;         UINT32 :20;           // Reserved
470         ;
471         mov     ecx, 0C0000408h         ; Read the family 10h mailbox
472         _RDMSR                          ;          MC4_MISC1[63:32]
473         mov     si, dx                  ;   SI = raw mailbox contents (will extract node# from this)
474         shr     ebx, 24                 ;   BL = CPUID Fn0000_0001_EBX[LocalApicId]
475         mov     di, bx                  ;   DI = Initial APIC ID (will extract core# from this)
476
477         AMD_CPUID   AMD_CPUID_APIC      ;
478         shr     ch, 4                   ;   CH = ApicIdSize, #bits in APIC ID that show core#
479         inc     cl                      ;   CL = Number of enabled cores in the socket
480         mov     bx, cx
481
482         mov     ecx, NB_CFG             ;   MSR:C001_001F
483         _RDMSR                          ;   EDX has InitApicIdCpuIdLo bit
484
485         mov     cl, bh                  ;   CL = APIC ID size
486         mov     al, 1                   ;   Convert APIC ID size to an AND mask
487         shl     al, cl                  ;   AL = 2^APIC ID size
488         dec     al                      ;   AL = mask for relative core number
489         xor     ah, ah                  ;   AX = mask for relative core number
490         bt      edx, (INIT_APIC_ID_CPU_ID_LO-32) ; InitApicIdCpuIdLo == 1?
491         .if (!carry?)                   ;   Br if yes
492             mov     ch, 8               ;   Calculate core number shift count
493             sub     ch, cl              ;   CH = core shift count
494             mov     cl, ch
495             shr     di, cl              ;   Right justify core number
496         .endif
497         and     di, ax                  ;   DI = socket-relative core number
498
499         mov     cx, si                  ;   CX = raw mailbox value
500         shr     cx, 10                  ;   CL[1:0] = ModuleType or #nodes per socket (0-SCM, 1-MCM)
501         and     cl, 3                   ;   Isolate ModuleType
502         xor     bh, bh                  ;   BX = Number of enabled cores in the socket
503         shr     bx, cl                  ;   BX = Number of enabled cores per node
504         xor     dx, dx                  ;   Clear upper word for div
505         mov     ax, di                  ;   AX = socket-relative core number
506         div     bx                      ;   DX = node-relative core number
507         movzx   eax, si                 ;   prepare return value (clears flags)
508         and     ax, 000Fh               ;   AX = node number
509         shl     ax, 8                   ;   [15:8]=node#
510         mov     al, dl                  ;   [7:0]=core# (relative to node)
511         mov     esi, eax                ;   ESI = return value
512     .endif                              ; end: Is_AP
513     bts     esi, FLAG_IS_PRIMARY        ; all Family 10h cores are primary
514
515 node_core_f10_exit:
516 ENDM
517
518
519 ;;***************************************************************************
520 ;;                      Family 12h MACROS
521 ;;***************************************************************************
522 ;---------------------------------------------------
523 ;
524 ; AMD_ENABLE_STACK_FAMILY_HOOK_F12 Macro - Stackless
525 ;
526 ;   Set any family specific controls needed to enable the use of
527 ;   cache as general storage before main memory is available.
528 ;
529 ; Inputs:
530 ;       ESI - node#, core#, flags from GET_NODE_ID_CORE_ID
531 ; Outputs:
532 ;       none
533 ;
534 ; Family 12h requirements (BKDG section 2.3.3):
535 ;   The following requirements must be satisfied prior to using the cache as general storage:
536 ;   * Paging must be disabled.
537 ;   * MSRC001_0015[INVD_WBINVD]=0
538 ;   * MSRC001_1020[DIS_SS]=1
539 ;   * MSRC001_1021[DIS_SPEC_TLB_RLD]=1
540 ;   * MSRC001_1022[DIS_SPEC_TLB_RLD]=1
541 ;   * MSRC001_1022[DIS_CLR_WBTOL2_SMC_HIT]=1
542 ;   * MSRC001_1022[DIS_HW_PF]=1
543 ;   * MSRC001_1029[ClflushSerialize]=1
544 ;   * No INVD or WBINVD, no exceptions, page faults or interrupts
545 ;---------------------------------------------------
546 AMD_ENABLE_STACK_FAMILY_HOOK_F12 MACRO
547     local   fam12_enable_stack_hook_exit
548
549     AMD_CPUID   CPUID_MODEL
550     shr     eax, 20                     ; AL = cpu extended family
551     cmp     al, 03h                     ; Is this family 12h?
552     jnz     fam12_enable_stack_hook_exit ; Br if no
553
554     mov     ecx, DC_CFG                 ; MSR:C001_1022
555     _RDMSR
556     bts     eax, DC_DIS_SPEC_TLB_RLD    ; Disable speculative DC-TLB reloads
557     bts     eax, DIS_CLR_WBTOL2_SMC_HIT ; Disable self modifying code check buffer
558     bts     eax, DIS_HW_PF              ; Disable hardware prefetches
559     _WRMSR
560
561     dec     cx   ;IC_CFG                ; MSR:C001_1021
562     _RDMSR
563     bts     eax, IC_DIS_SPEC_TLB_RLD    ; Disable speculative IC-TLB reloads
564     _WRMSR
565
566     dec     cx   ;LS_CFG                ; MSR:C001_1020
567     _RDMSR
568     bts     eax, DIS_SS                 ; Disabled Streaming store functionality
569     _WRMSR
570
571     mov     ecx, HWCR                   ; MSR C001_0015
572     _RDMSR
573     bt      esi, FLAG_STACK_REENTRY     ; Check if stack has already been set
574     .if (!carry?)
575         btr     eax, INVD_WBINVD        ;   disable INVD -> WBINVD conversion
576         _WRMSR
577     .endif
578
579     mov     ecx, DE_CFG                 ; MSR:C001_1029
580     _RDMSR
581     bts     eax, CL_FLUSH_SERIALIZE     ; Serialize all CL Flush actions
582     _WRMSR
583
584 fam12_enable_stack_hook_exit:
585 ENDM
586
587 ;----------------------------------------------
588 ;
589 ; AMD_DISABLE_STACK_FAMILY_HOOK_F12 Macro - Stackless
590 ;
591 ;   Return any family specific controls to their 'standard'
592 ;   settings for using cache with main memory.
593 ;
594 ; Inputs:
595 ;       ESI - [31:24] flags; [15,8]= Node#; [7,0]= core#
596 ; Outputs:
597 ;       none
598 ;
599 ; Family 12h requirements:
600 ;   * INVD or WBINVD
601 ;   * MSRC001_0015[INVD_WBINVD]=1
602 ;   * MSRC001_1020[DIS_SS]=0
603 ;   * MSRC001_1021[DIS_SPEC_TLB_RLD]=0
604 ;   * MSRC001_1022[DIS_SPEC_TLB_RLD]=0
605 ;   * MSRC001_1022[DIS_CLR_WBTOL2_SMC_HIT]=0
606 ;   * MSRC001_1022[DIS_HW_PF]=0
607 ;   * MSRC001_1029[ClflushSerialize]=0
608 ;---------------------------------------------------
609 AMD_DISABLE_STACK_FAMILY_HOOK_F12 MACRO
610     local   fam12_disable_stack_hook_exit
611
612     AMD_CPUID   CPUID_MODEL
613     shr     eax, 20                     ; AL = cpu extended family
614     cmp     al, 03h                     ; Is this family 12h?
615     jnz     fam12_disable_stack_hook_exit ; Br if no
616
617     mov     ecx, DC_CFG                 ; MSR:C001_1022
618     _RDMSR
619     btr     eax, DC_DIS_SPEC_TLB_RLD    ; Turn on speculative DC-TLB reloads
620     btr     eax, DIS_CLR_WBTOL2_SMC_HIT ; Enable self modifying code check buffer
621     btr     eax, DIS_HW_PF              ; Enable Hardware prefetches
622     _WRMSR
623
624     dec     cx   ;IC_CFG                ; MSR:C001_1021
625     _RDMSR
626     btr     eax, IC_DIS_SPEC_TLB_RLD    ; Turn on speculative IC-TLB reloads
627     _WRMSR
628
629     dec     cx   ;LS_CFG                ; MSR:C001_1020
630     _RDMSR
631     btr     eax, DIS_SS                 ; Turn on Streaming store functionality
632     _WRMSR
633
634     mov     ecx, DE_CFG                 ; MSR:C001_1029
635     _RDMSR
636     btr     eax, CL_FLUSH_SERIALIZE
637     _WRMSR
638
639     ;--------------------------------------------------------------------------
640     ; Begin critical sequence in which EAX, BX, ECX, and EDX must be preserved.
641     ;--------------------------------------------------------------------------
642
643     mov     ecx, HWCR                    ; MSR:0000_0015h
644     _RDMSR
645     mov     bx, ax                      ; Save INVD -> WBINVD bit
646     btr     eax, INVD_WBINVD            ; Disable INVD -> WBINVD conversion
647     _WRMSR
648     invd                                ; Clear the cache tag RAMs
649     mov     ax, bx                      ; Restore INVD -> WBINVD bit
650     _WRMSR
651
652     ;--------------------------------------------------------------------------
653     ; End critical sequence in which EAX, BX, ECX, and EDX must be preserved.
654     ;--------------------------------------------------------------------------
655
656 fam12_disable_stack_hook_exit:
657 ENDM
658
659 ;---------------------------------------------------
660 ;
661 ; GET_NODE_ID_CORE_ID_F12 Macro - Stackless
662 ;
663 ;   Read family specific values to determine the node and core
664 ;   numbers for the core executing this code.
665 ;
666 ; Inputs:
667 ;     none
668 ; Outputs:
669 ;     SI = core#, node# & flags (see GET_NODE_ID_CORE_ID macro above)
670 ;---------------------------------------------------
671 GET_NODE_ID_CORE_ID_F12 MACRO
672
673     local   node_core_f12_exit
674
675     cmp     si, -1                      ; Has node/core already been discovered?
676     jnz     node_core_f12_exit          ; Br if yes
677
678     AMD_CPUID   CPUID_MODEL
679     shr     eax, 20                     ; AL = cpu extended family
680     cmp     al, 03h                     ; Is this family 12h?
681     jnz     node_core_f12_exit          ; Br if no
682
683     shr     ebx, 24                     ; CPUID_0000_0001_EBX[31:24]: initial local APIC physical ID
684     bts     ebx, FLAG_IS_PRIMARY        ; all family 12h cores are primary
685     mov     esi, ebx                    ; ESI = Node#=0, core number
686 node_core_f12_exit:
687 ENDM
688
689
690 ;;***************************************************************************
691 ;;                      Family 14h MACROS
692 ;;***************************************************************************
693 ;---------------------------------------------------
694 ;
695 ; AMD_ENABLE_STACK_FAMILY_HOOK_F14 Macro - Stackless
696 ;
697 ;   Set any family specific controls needed to enable the use of
698 ;   cache as general storage before main memory is available.
699 ;
700 ; Inputs:
701 ;       ESI - node#, core#, flags from GET_NODE_ID_CORE_ID
702 ; Outputs:
703 ;       none
704 ;
705 ; Family 14h requirements (BKDG section 2.3.3):
706 ;   * Paging must be disabled.
707 ;   * MSRC001_0015[INVD_WBINVD]=0.
708 ;   * MSRC001_1020[DisStreamSt]=1.
709 ;   * MSRC001_1021[DIS_SPEC_TLB_RLD]=1. Disable speculative ITLB reloads.
710 ;   * MSRC001_1022[DIS_HW_PF]=1.
711 ;   * No INVD or WBINVD, no exceptions, page faults or interrupts
712 ;---------------------------------------------------
713 AMD_ENABLE_STACK_FAMILY_HOOK_F14 MACRO
714     local   fam14_enable_stack_hook_exit
715
716     AMD_CPUID   CPUID_MODEL
717     shr     eax, 20                     ; AL = cpu extended family
718     cmp     al, 05h                     ; Is this family 14h?
719     jnz     fam14_enable_stack_hook_exit ; Br if no
720
721     mov     ecx, DC_CFG                 ; MSR:C001_1022
722     _RDMSR
723     bts     eax, DIS_HW_PF              ; Disable hardware prefetches
724     _WRMSR
725
726     dec     cx  ;IC_CFG                 ; MSR:C001_1021
727     _RDMSR
728     bts     eax, IC_DIS_SPEC_TLB_RLD    ; Disable speculative TLB reloads
729     _WRMSR
730
731     dec     cx  ;LS_CFG                 ; MSR:C001_1020
732     _RDMSR
733     bts     eax, DIS_STREAM_ST          ; Disabled Streaming store functionality
734     _WRMSR
735
736     mov     ecx, HWCR                   ; MSR C001_0015
737     _RDMSR
738     bt      esi, FLAG_STACK_REENTRY     ; Check if stack has already been set
739     .if (!carry?)
740         btr     eax, INVD_WBINVD        ; disable INVD -> WBINVD conversion
741         _WRMSR
742     .endif
743
744 fam14_enable_stack_hook_exit:
745 ENDM
746
747 ;----------------------------------------------
748 ;
749 ; AMD_DISABLE_STACK_FAMILY_HOOK_F14 Macro - Stackless
750 ;
751 ;   Return any family specific controls to their 'standard'
752 ;   settings for using cache with main memory.
753 ;
754 ; Inputs:
755 ;       ESI - [31:24] flags; [15,8]= Node#; [7,0]= core#
756 ; Outputs:
757 ;       none
758 ;
759 ; Family 14h requirements:
760 ;   * INVD or WBINVD
761 ;   * MSRC001_0015[INVD_WBINVD]=1.
762 ;   * MSRC001_1020[DisStreamSt]=0.
763 ;   * MSRC001_1021[DIS_SPEC_TLB_RLD]=0.
764 ;   * MSRC001_1022[DIS_HW_PF]=0.
765 ;---------------------------------------------------
766 AMD_DISABLE_STACK_FAMILY_HOOK_F14 MACRO
767     local   fam14_disable_stack_hook_exit
768
769     AMD_CPUID   CPUID_MODEL
770     shr     eax, 20                     ; AL = cpu extended family
771     cmp     al, 05h                     ; Is this family 14h?
772     jnz     fam14_disable_stack_hook_exit ; Br if no
773
774     mov     ecx, LS_CFG                 ; MSR:C001_1020
775     _RDMSR
776     btr     eax, DIS_STREAM_ST          ; Turn on Streaming store functionality
777     _WRMSR
778
779     inc     cx  ;IC_CFG                 ; MSR:C001_1021
780     _RDMSR
781     btr     eax, IC_DIS_SPEC_TLB_RLD    ; Turn on speculative DC-TLB reloads
782     _WRMSR
783
784     inc     cx  ;DC_CFG                 ; MSR:C001_1022
785     _RDMSR
786     btr     eax, DIS_HW_PF              ; Turn on hardware prefetches
787     _WRMSR
788
789     ;--------------------------------------------------------------------------
790     ; Begin critical sequence in which EAX, BX, ECX, and EDX must be preserved.
791     ;--------------------------------------------------------------------------
792
793     mov     ecx, HWCR                    ; MSR:C001_0015h
794     _RDMSR
795     btr     eax, INVD_WBINVD            ; Disable INVD -> WBINVD conversion
796     _WRMSR
797     invd                                ; Clear the cache tag RAMs
798     bts     eax, INVD_WBINVD            ; Turn on Conversion of INVD to WBINVD
799     _WRMSR
800
801     ;--------------------------------------------------------------------------
802     ; End critical sequence in which EAX, BX, ECX, and EDX must be preserved.
803     ;--------------------------------------------------------------------------
804
805 fam14_disable_stack_hook_exit:
806 ENDM
807
808 ;---------------------------------------------------
809 ;
810 ; GET_NODE_ID_CORE_ID_F14 Macro - Stackless
811 ;
812 ;   Read family specific values to determine the node and core
813 ;   numbers for the core executing this code.
814 ;
815 ; Inputs:
816 ;     none
817 ; Outputs:
818 ;     SI = core#, node# & flags (see GET_NODE_ID_CORE_ID macro above)
819 ;---------------------------------------------------
820 GET_NODE_ID_CORE_ID_F14 MACRO
821
822     local   node_core_f14_exit
823
824     cmp     si, -1                      ; Has node/core already been discovered?
825     jnz     node_core_f14_exit          ; Br if yes
826
827     AMD_CPUID   CPUID_MODEL
828     shr     eax, 20                     ; AL = cpu extended family
829     cmp     al, 05h                     ; Is this family 14h?
830     jnz     node_core_f14_exit          ; Br if no
831
832     xor     esi, esi                    ; Node must be 0
833     bts     esi, FLAG_IS_PRIMARY        ; all family 14h cores are primary
834     mov     ecx, APIC_BASE_ADDRESS      ; MSR:0000_001B
835     _RDMSR
836     bt      eax, APIC_BSC               ;
837     .if (!carry?)                       ; Is this the BSC?
838                                         ;   No, this is an AP
839         inc     si                      ;   Set core to 1
840     .endif                              ;
841 node_core_f14_exit:
842 ENDM
843
844
845
846 ;;***************************************************************************
847 ;;                      Family 15h MACROS
848 ;;***************************************************************************
849 ;---------------------------------------------------
850 ;
851 ; AMD_ENABLE_STACK_FAMILY_HOOK_F15 Macro - Stackless
852 ;
853 ;   Set any family specific controls needed to enable the use of
854 ;   cache as general storage before main memory is available.
855 ;
856 ; Inputs:
857 ;       ESI - node#, core#, flags from GET_NODE_ID_CORE_ID
858 ; Outputs:
859 ;       none
860 ;
861 ; Family 15h requirements (BKDG #42301 section 2.3.3):
862 ;   * Paging must be disabled.
863 ;   * MSRC001_0015[INVD_WBINVD]=0
864 ;   * MSRC001_1020[DisSS]=1
865 ;   * MSRC001_1021[DIS_SPEC_TLB_RLD]=1
866 ;   * MSRC001_1022[DIS_SPEC_TLB_RLD]=1
867 ;   * MSRC001_1022[DisHwPf]=1
868 ;   * No INVD or WBINVD, no exceptions, page faults or interrupts
869 ;---------------------------------------------------
870 AMD_ENABLE_STACK_FAMILY_HOOK_F15 MACRO
871     local   fam15_enable_stack_hook_exit
872
873     AMD_CPUID   CPUID_MODEL
874     shr     eax, 20                     ; AL = cpu extended family
875     cmp     al, 06h                     ; Is this family 15h?
876     jnz     fam15_enable_stack_hook_exit ; Br if no
877
878     bt      esi, FLAG_STACK_REENTRY     ; Check if stack has already been set
879     .if (!carry?)
880         mov     ecx, HWCR                   ; MSR C001_0015
881         _RDMSR
882         btr     eax, INVD_WBINVD        ; disable INVD -> WBINVD conversion
883         _WRMSR
884     .endif
885
886     mov     ecx, LS_CFG                 ; MSR:C001_1020
887     _RDMSR
888     bts     eax, DIS_SS                 ; Turn on Streaming store functionality disabled bit
889     _WRMSR
890
891     inc     ecx  ;IC_CFG                ; MSR:C001_1021
892     _RDMSR
893     bts     eax, IC_DIS_SPEC_TLB_RLD    ; Turn on Disable speculative IC-TLB reloads bit
894     _WRMSR
895
896     inc     ecx  ;DC_CFG                ; MSR:C001_1022
897     _RDMSR
898     bts     eax, DC_DIS_SPEC_TLB_RLD    ; Turn on Disable speculative DC-TLB reloads bit
899     bts     eax, DIS_HW_PF              ; Turn on Disable hardware prefetches bit
900     _WRMSR
901
902     mov     ecx, CU_CFG3                ; MSR:C001_102B
903     _RDMSR
904     btr     edx, (COMBINE_CR0_CD - 32)  ; Clear CombineCr0Cd bit
905     _WRMSR
906
907 fam15_enable_stack_hook_exit:
908 ENDM
909
910
911 ;----------------------------------------------
912 ;
913 ; AMD_DISABLE_STACK_FAMILY_HOOK_F15 Macro - Stackless
914 ;
915 ;   Return any family specific controls to their 'standard'
916 ;   settings for using cache with main memory.
917 ;
918 ; Inputs:
919 ;       ESI - [31:24] flags; [15,8]= Node#; [7,0]= core#
920 ; Outputs:
921 ;       none
922 ;
923 ; Family 15h requirements:
924 ;   * INVD or WBINVD
925 ;   * MSRC001_0015[INVD_WBINVD]=1
926 ;   * MSRC001_1020[DisSS]=0
927 ;   * MSRC001_1021[DIS_SPEC_TLB_RLD]=0
928 ;   * MSRC001_1022[DIS_SPEC_TLB_RLD]=0
929 ;   * MSRC001_1022[DIS_HW_PF]=0
930 ;---------------------------------------------------
931 AMD_DISABLE_STACK_FAMILY_HOOK_F15 MACRO
932     local   fam15_disable_stack_hook_exit
933
934     AMD_CPUID   CPUID_MODEL
935     mov     ebx, eax                    ; Save revision info to EBX
936     shr     eax, 20                     ; AL = cpu extended family
937     cmp     al, 06h                     ; Is this family 15h?
938     jnz     fam15_disable_stack_hook_exit ; Br if no
939
940     mov     ecx, LS_CFG                 ; MSR:C001_1020
941     .if (ebx != 00600F00h)              ; Is this rev A0?
942         _RDMSR
943         btr     eax, DIS_SS             ; Turn on Streaming store functionality
944         _WRMSR
945     .endif                              ; End workaround for errata 495 and 496
946
947     inc     ecx  ;IC_CFG                ; MSR:C001_1021
948     _RDMSR
949     btr     eax, IC_DIS_SPEC_TLB_RLD    ; Turn on speculative TLB reloads
950     _WRMSR
951
952     inc     ecx  ;DC_CFG                ; MSR:C001_1022
953     _RDMSR
954     btr     eax, DC_DIS_SPEC_TLB_RLD    ; Turn on speculative TLB reloads
955     .if (ebx != 00600F00h)              ; Is this rev A0?
956         btr     eax, DIS_HW_PF          ; Turn on hardware prefetches
957     .endif                              ; End workaround for erratum 498
958     _WRMSR
959
960     ;--------------------------------------------------------------------------
961     ; Begin critical sequence in which EAX, BX, ECX, and EDX must be preserved.
962     ;--------------------------------------------------------------------------
963
964     bt      esi, FLAG_IS_PRIMARY
965     .if (carry?)                        ; Only clear cache from primary core
966         mov     ecx, HWCR               ;   MSR:C001_0015h
967         _RDMSR
968         btr     eax, INVD_WBINVD        ;   Disable INVD -> WBINVD conversion
969         _WRMSR
970         invd                            ;   Clear the cache tag RAMs
971         bts     eax, INVD_WBINVD        ;   Turn on Conversion of INVD to WBINVD
972         _WRMSR
973     .endif                              ; end
974
975     ;--------------------------------------------------------------------------
976     ; End critical sequence in which EAX, BX, ECX, and EDX must be preserved.
977     ;--------------------------------------------------------------------------
978
979     mov     ecx, CU_CFG3                ; MSR:C001_102B
980     _RDMSR
981     bts     edx, (COMBINE_CR0_CD - 32)  ; Set CombineCr0Cd bit
982     _WRMSR
983
984 fam15_disable_stack_hook_exit:
985 ENDM
986
987
988 ;---------------------------------------------------
989 ;
990 ; GET_NODE_ID_CORE_ID_F15 Macro - Stackless
991 ;
992 ;   Read family specific values to determine the node and core
993 ;   numbers for the core executing this code.
994 ;
995 ; Inputs:
996 ;     none
997 ; Outputs:
998 ;     SI = core#, node# & flags (see GET_NODE_ID_CORE_ID macro above)
999 ;---------------------------------------------------
1000 GET_NODE_ID_CORE_ID_F15 MACRO
1001
1002     local   node_core_f15_exit
1003
1004     cmp     si, -1                      ; Has node/core already been discovered?
1005     jnz     node_core_f15_exit          ; Br if yes
1006
1007     AMD_CPUID   CPUID_MODEL
1008     shr     eax, 20                     ; AL = cpu extended family
1009     cmp     al, 06h                     ; Is this family 15h?
1010     jnz     node_core_f15_exit          ; Br if no
1011
1012     xor     esi, esi                    ; Assume BSC, clear local flags
1013     mov     ecx, APIC_BASE_ADDRESS      ; MSR:0000_001B
1014     _RDMSR
1015     bt      eax, APIC_BSC               ; Is this the BSC?
1016     .if (carry?)
1017         ; This is the BSP.
1018         ; Enable routing tables on BSP (just in case the HT init code has not yet enabled them)
1019         mov     eax, 8000C06Ch          ;   PCI address for D18F0x6C Link Initialization Control Register
1020         mov     dx, 0CF8h
1021         out     dx, eax
1022         add     dx, 4
1023         in      eax, dx
1024         btr     eax, 0                  ;   Set LinkInitializationControl[RouteTblDis] = 0
1025         out     dx, eax
1026     .else                               ;
1027         ; This is an AP. Routing tables have been enabled by the HT Init process.
1028         ; Also, the MailBox register was set by the BSP during early init
1029         ;   The Mailbox register content is formatted as follows:
1030         ;         UINT32 Node:4;        // The node id of Core's node.
1031         ;         UINT32 Socket:4;      // The socket of this Core's node.
1032         ;         UINT32 Module:2;      // The internal module number for Core's node.
1033         ;         UINT32 ModuleType:2;  // Single Module = 0, Multi-module = 1.
1034         ;         UINT32 :20;           // Reserved
1035         ;
1036         mov     ecx, 0C0000408h         ;   Read the family 15h mailbox
1037         _RDMSR                          ;      MC4_MISC1[63:32]
1038         mov     si, dx                  ;   SI = raw mailbox contents (will extract node# from this)
1039         shr     ebx, 24                 ;   BL = CPUID Fn0000_0001_EBX[LocalApicId]
1040         mov     di, bx                  ;   DI = Initial APIC ID (will extract core# from this)
1041
1042         AMD_CPUID   AMD_CPUID_APIC      ;
1043         shr     ch, 4                   ;   CH = ApicIdSize, #bits in APIC ID that show core#
1044         inc     cl                      ;   CL = Number of enabled cores in the socket
1045         mov     bx, cx
1046
1047         mov     ecx, NB_CFG
1048         _RDMSR                          ;   EDX has InitApicIdCpuIdLo bit
1049
1050         mov     cl, bh                  ;   CL = APIC ID size
1051         mov     al, 1                   ;   Convert APIC ID size to an AND mask
1052         shl     al, cl                  ;   AL = 2^APIC ID size
1053         dec     al                      ;   AL = mask for relative core number
1054         xor     ah, ah                  ;   AX = mask for relative core number
1055         bt      edx, (INIT_APIC_ID_CPU_ID_LO-32) ; InitApicIdCpuIdLo == 1?
1056         .if (!carry?)                   ;   Br if yes
1057             mov     ch, 8               ;     Calculate core number shift count
1058             sub     ch, cl              ;     CH = core shift count
1059             mov     cl, ch              ;
1060             shr     di, cl              ;     Right justify core number
1061         .endif                          ;
1062         and     di, ax                  ;   DI = socket-relative core number
1063
1064         mov     cx, si                  ;   CX = raw mailbox value
1065         shr     cx, 10                  ;   CL[1:0] = ModuleType or #nodes per socket (0-SCM, 1-MCM)
1066         and     cl, 3                   ;   Isolate ModuleType
1067         xor     bh, bh                  ;   BX = Number of enabled cores in the socket
1068         shr     bx, cl                  ;   BX = Number of enabled cores per node
1069         xor     dx, dx                  ;   Clear upper word for div
1070         mov     ax, di                  ;   AX = socket-relative core number
1071         div     bx                      ;   DX = node-relative core number
1072         movzx   eax, si                 ;   Prepare return value
1073         and     ax, 000Fh               ;   AX = node number
1074         shl     ax, 8                   ;   [15:8]=node#
1075         mov     al, dl                  ;   [7:0]=core# (relative to node)
1076         mov     esi, eax                ;   ESI = node-relative core number
1077     .endif                              ; end
1078
1079     ;
1080     ;   determine if this core shares MTRRs
1081     ;
1082     mov     eax, 8000C580h              ; Compute Unit Status
1083     mov     bx, si                      ; load node#(bh), core#(bl)
1084     shl     bh, 3                       ; Move node# to PCI Dev# field
1085     add     ah, bh                      ; Adjust PCI adress for node number
1086     mov     dx, 0CF8h
1087     out     dx, eax
1088     add     dx, 4
1089     in      eax, dx                     ; [3:0]=Enabled; [19:16]=DualCore
1090     ;
1091                                         ; BL is MyCore#  , BH is primary flag
1092     mov     cx, 06h                     ; Use CH as 'first of pair' core#
1093     .while (cl > 0)
1094         bt      eax, 0                  ;   Is pair enabled?
1095         .if (carry?)                    ;
1096             mov     bh, 01h             ;   flag core as primary
1097             bt      eax, 16             ;   Is there a 2nd in the pair?
1098             .if (carry?)                ;
1099                 .break .if (ch == bl)   ;     Does 1st match MyCore#?
1100                 inc     ch
1101                 xor     bh, bh          ;     flag core as NOT primary
1102                 .break .if (ch == bl)   ;     Does 2nd match MyCore#?
1103             .else                       ;   No 2nd core
1104                 .break .if (ch == bl)   ;     Does 1st match MyCore#?
1105             .endif
1106             inc     ch
1107         .endif
1108         shr     eax, 1
1109         dec     cl
1110     .endw
1111     .if (cl == 0)
1112         ;Error - core# didn't match Compute Unit Status content
1113         bts     esi, FLAG_UNKNOWN_FAMILY
1114         bts     esi, FLAG_IS_PRIMARY    ;   Set Is_Primary for unknowns
1115     .endif
1116     .if (bh != 0)                       ; Check state of primary for the matched core
1117         bts     esi, FLAG_IS_PRIMARY    ;   Set shared flag into return value
1118     .endif
1119     ;
1120 node_core_f15_exit:
1121 ENDM
1122
1123
1124