AGESA F15: AMD family15 AGESA code
[coreboot.git] / src / vendorcode / amd / agesa / f15 / Legacy / bridge32.inc
1 ; ****************************************************************************
2 ; *
3 ; * @file
4 ; *
5 ; * Agesa structures and definitions
6 ; *
7 ; * Contains AMD AGESA core interface
8 ; *
9 ; * @xrefitem bom "File Content Label" "Release Content"
10 ; * @e project:      AGESA
11 ; * @e sub-project:  Include
12 ; * @e \$Revision: 44324 $   @e \$Date: 2010-12-22 02:16:51 -0700 (Wed, 22 Dec 2010) $
13 ;
14 ; ****************************************************************************
15 ;
16 ; Copyright (C) 2012 Advanced Micro Devices, Inc.
17 ; All rights reserved.
18 ;
19 ; Redistribution and use in source and binary forms, with or without
20 ; modification, are permitted provided that the following conditions are met:
21 ;     * Redistributions of source code must retain the above copyright
22 ;       notice, this list of conditions and the following disclaimer.
23 ;     * Redistributions in binary form must reproduce the above copyright
24 ;       notice, this list of conditions and the following disclaimer in the
25 ;       documentation and/or other materials provided with the distribution.
26 ;     * Neither the name of Advanced Micro Devices, Inc. nor the names of
27 ;       its contributors may be used to endorse or promote products derived
28 ;       from this software without specific prior written permission.
29 ;
30 ; THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND
31 ; ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
32 ; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
33 ; DISCLAIMED. IN NO EVENT SHALL ADVANCED MICRO DEVICES, INC. BE LIABLE FOR ANY
34 ; DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES
35 ; (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
36 ; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND
37 ; ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
38 ; (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS
39 ; SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
40 ;
41 ;*****************************************************************************
42
43 PARAM1          textequ <[bp+8]>
44 PARAM2          textequ <[bp+12]>
45 PARAM3          textequ <[bp+16]>
46 RETAddress      textequ <[bp+4]>
47
48 AMD_PRIVATE_PARAMS STRUCT
49     Gate16_CS   DW ?                ; Segment of AMD_BRIDGE_32 and AMD_CALLOUT_16
50     Gate16_SS   DW ?                ; RM stack segment
51     Router_Seg  DW ?                ; Segment of oem router
52     Router_Off  DW ?                ; Offset of oem router
53 AMD_PRIVATE_PARAMS ENDS
54
55 ; OEM may pre-define the GDT and selector offsets. If they do not, use our defaults.
56 IFNDEF  AGESA_SELECTOR_GDT
57         AGESA_SELECTOR_GDT         EQU 00h
58 ENDIF
59 IFNDEF  AGESA_SELECTOR_CODE16
60         AGESA_SELECTOR_CODE16      EQU 08h
61 ENDIF
62 IFNDEF  AGESA_SELECTOR_DATA16
63         AGESA_SELECTOR_DATA16      EQU 10h
64 ENDIF
65 IFNDEF  AGESA_SELECTOR_CODE32
66         AGESA_SELECTOR_CODE32      EQU 18h
67 ENDIF
68 IFNDEF  AGESA_SELECTOR_DATA32
69         AGESA_SELECTOR_DATA32      EQU 20h
70 ENDIF
71
72
73 AMD_BRIDGE_32_GDT MACRO  GDT_Name:REQ
74
75         GDT_Name LABEL BYTE
76             DD 000000000h, 000000000h       ; NULL descriptor
77             DD 00000ffffh, 000009b00h       ; 16-bit code, fixed up
78             DD 00000ffffh, 000009300h       ; 16-bit data, fixed up
79             DD 00000ffffh, 000CF9B00h       ; 32-bit protected mode code
80             DD 00000ffffh, 000CF9300h       ; 32-bit protected mode data
81         GDT_Length EQU ($-GDT_Name)
82
83 ENDM
84
85 ;+-------------------------------------------------------------------------
86 ;
87 ;       AMD_BRIDGE_32 - Execute Agesa through Pushhigh interface
88 ;
89 ;   Processing:
90 ;       The following steps are taken:
91 ;       1) Enter 32bit Protected Mode (PM32)
92 ;       2) Run AGESA code
93 ;       3) Restore Real Mode (RM)
94 ;
95 ; Entry:
96 ;       [big real mode] : ds, es set to base 0 limit 4G segment
97 ;       EDX - if not 0, provides a FAR PTR to oem router (Seg | Offset)
98 ;       ESI - configuration block pointer
99 ;
100 ; Exit:
101 ;       EAX - return value
102 ;       ESI - configuration block pointer
103 ;       ds, es, fs, gs - Set to 4GB segment limit for Big Real Mode
104 ;
105 ; Modified:
106 ;      None
107 ;
108
109 AMD_BRIDGE_32 MACRO GDT_Name
110
111         local   copyGDT
112         local   flushTo16PM
113         local   agesaReturnAddress
114         local   leave32bitPM
115         local   flush2RM
116
117         push    gs
118         push    fs
119         push    ebx
120         push    ecx
121         push    edi
122         mov     eax, esp
123         push    eax
124         movzx   esp, sp
125 ;
126 ; Do not use any locals here, BP will be changed frequently during RM->PM32->RM
127 ;
128         pushf
129         cli                         ; Disable interrupts during AGESA
130         cld                         ; Need known direction flag during AGESA
131
132 ;
133 ; Save the FAR PTR input parameter
134 ;
135         mov     gs, dx                  ; Offset
136         shr     edx, 16
137         mov     fs, dx                  ; Segment
138 ;
139 ; Determine where our binary file is and get entry point
140 ;
141         mov     edx, (AMD_CONFIG_PARAMS PTR [esi]).ImageBasePtr
142         add     edx, (AMD_IMAGE_HEADER PTR [edx]).EntryPointAddress
143 ;
144 ; Figure out the return address we will use after calling AGESA
145 ; and store it in ebx until we have our stack set up properly
146 ;
147         mov     ebx, cs
148         shl     ebx, 4
149         add     ebx, OFFSET agesaReturnAddress
150 ;
151 ; Save our current RM stack AND entry EBP
152 ;
153         push    ebp
154 ;       push    esp
155         push    ss
156
157 ;
158 ; BEGIN --- STACK MUST BE BALANCED AT THIS POINT --- BEGIN
159 ;
160 ; Copy the GDT onto the stack for modification
161 ;
162         mov     cx, GDT_Length
163         sub     sp, cx
164         mov     bp, sp
165         lea     di, GDT_Name
166 copyGDT:
167         mov     al, cs:[di]
168         mov     [bp], al
169         inc     di
170         inc     bp
171         loop    copyGDT
172 ;
173 ; Patch 16-bit code and data descriptors on stack.  We will
174 ; fix up CS and SS for PM16 during the callout if applicable.
175 ;
176         mov     bp, sp
177
178         mov     eax, cs
179         shl     eax, 4
180         mov     [bp+AGESA_SELECTOR_CODE16+2], ax
181         shr     eax, 16
182         mov     [bp+AGESA_SELECTOR_CODE16+4], al
183
184         mov     eax, ss
185         shl     eax, 4
186         mov     [bp+AGESA_SELECTOR_DATA16+2], ax
187         shr     eax, 16
188         mov     [bp+AGESA_SELECTOR_DATA16+4], al
189 ;
190 ; Need to place Length and Address on GDT
191 ;
192         mov     eax, ss
193         shl     eax, 4
194         add     eax, esp
195         push    eax
196         push    WORD PTR (GDT_Length-1)
197 ;
198 ; Load the GDT
199 ;
200         mov     bp, sp
201         lgdt    FWORD PTR [bp]
202 ;
203 ; TABLE 1
204 ;
205 ; Place PRIVATE DATA on stack DIRECTLY following GDT
206 ; During this routine, stack data is critical.  If
207 ; order is changed or additional added, bad things
208 ; will happen!
209 ;
210 ; HIGHEST PHYSICAL ADDRESS
211 ;
212 ; | ...                  |
213 ; ------------------------
214 ; | old RM SP            |
215 ; | old RM SS            |
216 ; ------------------------ sp + SIZEOF AMD_PRIVATE_PARAMS + (SIZEOF GDT_LENGTH + 6 {size, address})
217 ; | GDT_DATA32           |
218 ; | ...                  |
219 ; | GDT_NULL             |
220 ; | GDT Addr, Length     |
221 ; ------------------------ sp + SIZEOF AMD_PRIVATE_PARAMS
222 ; | Priv.Gate16_SS       |
223 ; | Priv.Gate16_CS       |
224 ; ------------------------ sp
225 ; ------ THEN PUSH -------
226 ; | Return to 16-bit CS  |
227 ; | Return to 16-bit Off |
228 ; | ...                  |
229 ;
230 ; LOWEST  PHYSICAL ADDRESS
231 ;
232         mov     edi, esp
233         sub     edi, SIZEOF AMD_PRIVATE_PARAMS
234         mov     ax, cs
235         mov     (AMD_PRIVATE_PARAMS PTR ss:[edi]).Gate16_CS, ax
236         mov     ax, ss
237         mov     (AMD_PRIVATE_PARAMS PTR ss:[edi]).Gate16_SS, ax
238         mov     (AMD_PRIVATE_PARAMS PTR ss:[edi]).Router_Off, gs
239         mov     (AMD_PRIVATE_PARAMS PTR ss:[edi]).Router_Seg, fs
240
241         mov     esp, edi
242 ;
243 ; Save an address for returning to 16 bit real mode on stack,
244 ; we'll use it in a far ret after turning off CR0.PE so that
245 ; we can take our address off and force a far jump.  Be sure
246 ; no unexpected data is on the stack after this!
247 ;
248         mov     ax, cs
249         push    cs
250         lea     ax, flush2RM
251         push    ax
252 ;
253 ; Convert ss:esp to "flat"
254 ;
255
256         mov     ax, sp
257         push    ax
258         mov     eax, ss
259         shl     eax, 4
260         add     eax, esp
261         mov     esp, eax                ; Load the zero based ESP
262
263 ;
264 ; Set CR0.PE
265 ;
266         mov     eax, CR0                ; Get CPU control word 0
267         or      al, 01                  ; Enable CPU protected mode
268         mov     CR0, eax                ; Write back to CPU control word 0
269         jmp     flushTo16PM
270
271 flushTo16PM:
272 ;
273 ; 16-bit protected mode
274 ;
275         mov     ax, AGESA_SELECTOR_DATA32
276         mov     ds, ax
277         mov     es, ax
278         mov     fs, ax
279         mov     gs, ax
280         mov     ss, ax
281 ;
282 ; Push our parameters RIGHT TO LEFT, and then return address
283 ;
284         push    esi                     ; AGESA configuration block pointer (data)
285         push    ebx                     ; after AGESA return offset (32PM flat) - consumed by dispatcher ret
286         pushd   AGESA_SELECTOR_CODE32   ; AGESA entry selector (32PM flat)
287         push    edx                     ; AGESA entry point (32PM flat)
288
289         DB      066h
290         retf                            ; <><><> Enter AGESA 32-bit code!!! <><><>
291
292 agesaReturnAddress:
293 ;
294 ; Returns from the Agesa 32-bit code still PM32
295 ;
296         DB      0EAh
297         DD      OFFSET leave32bitPM
298         DW      AGESA_SELECTOR_CODE16
299
300 leave32bitPM:
301 ;
302 ; Now in 16-bit PM
303 ;
304         add     esp, 4                  ; +4 to remove our config block pointer
305 ;
306 ; Eax reserve AGESA_STATUS return code, save it
307 ;
308         mov     ebx, eax
309 ;
310 ; Turn off CR0.PE, restore 64K stack limit
311 ;
312         pop     ax
313         mov     sp, ax
314         mov     ax, AGESA_SELECTOR_DATA16
315         mov     ss, ax
316
317         mov     eax, CR0
318         and     al, NOT 1               ; Disable protected mode
319         mov     CR0, eax                ; Write back CR0.PE
320 ;
321 ; Jump far to enter RM, we saved this address on the stack
322 ; already.  Hopefully stack is balanced through AGESA
323 ; nor were any params added by pushing them on the stack and
324 ; not removing them between BEGIN-END comments.
325 ;
326         retf
327
328 flush2RM:
329 ;
330 ; Set segments registers for big real mode before returning
331 ;
332         xor     ax, ax
333         mov     ds, ax
334         mov     es, ax
335         mov     fs, ax
336         mov     gs, ax
337 ;
338 ; Discard GDT, +6 for GDT pointer/size, privates
339 ;
340         add     esp, GDT_Length + 6 + SIZEOF AMD_PRIVATE_PARAMS
341 ;
342 ; Restore real mode stack and entry EBP
343 ;
344         pop     cx
345 ;       mov     esp, [esp]
346         mov     ss, cx
347         pop     ebp
348 ;
349 ; Restore AGESA_STATUS return code to eax
350 ;
351         mov     eax, ebx
352 ;
353 ; END --- STACK MUST BE BALANCED TO THIS POINT --- END
354 ;
355
356         popf
357         pop     ebx
358         mov     esp, ebx
359         pop     edi
360         pop     ecx
361         pop     ebx
362         pop     fs
363         pop     gs
364                             ; EXIT AMD_BRIDGE_32
365 ENDM
366 ;+-------------------------------------------------------------------------
367 ;
368 ; AMD_CALLOUT_16 - Execute Callback from Pushhigh interface
369 ;
370 ;   Processing:
371 ;       The following steps are taken:
372 ;       1) Enter PM16
373 ;       2) Setup stack, get private params
374 ;       3) Enter RM
375 ;       4) Get 3 params
376 ;       5) Call oemCallout OR oem router
377 ;       6) Enter PM32
378 ;       7) Return to Agesa PH
379 ;
380 ; Entry:
381 ;       [32-bit protected mode]
382 ;       [esp+8] Func
383 ;       [esp+12] Data
384 ;       [esp+16] Configuration Block
385 ;       [esp+4] return address to Agesa
386 ;
387 ; Exit:
388 ;       [32-bit protected mode]
389 ;
390 ; Modified:
391 ;     None
392 ;
393 AMD_CALLOUT_16 MACRO  LocalOemCalloutRouter
394 ;
395 ; Note that we are still PM32, so MASM may work strangely
396 ;
397
398         push    bp                     ; Save our original SP to access params
399         mov     bp, sp
400         push    bx
401         push    si
402         push    di
403         push    cx
404         push    dx
405         push    di
406
407         DB      066h, 0EAh
408         DW      OFFSET PM16Entry
409         DW      AGESA_SELECTOR_CODE16
410
411 PM16Entry:
412 ;
413 ; PM16 CS, but still PM32 SS, as we need to access our private params
414 ; before we enter RM.
415 ;
416 ; Note: we are working below the stack temporarily, and and it will
417 ; not affect our ability to get entry params
418 ;
419         xor     ecx, ecx
420         xor     edx, edx
421 ;
422 ; SGDT will give us the original location of the GDT on our CAS stack.
423 ; We need this value because our private parameters are located just
424 ; below the GDT.
425 ;
426         mov     edi, esp
427         sub     edi, GDT_Length + 6
428         sgdt    FWORD PTR [edi]        ; [edi] = word size, dword address
429         mov     edi, DWORD PTR [edi+2]  ; Get the PM32 address only
430         sub     edi, SIZEOF AMD_PRIVATE_PARAMS + 6
431 ;
432 ; cx = code segment of this code in RM
433 ; dx = stack segment of CAS in RM
434 ; fs = code segment of oem router (save for later)
435 ; gs = offset of oem router (save for later)
436 ; fs and gs are loaded after switch to real mode because we can't
437 ; use them as scratch pad registers in protected mode
438 ;
439         mov     cx, (AMD_PRIVATE_PARAMS PTR ss:[edi]).Gate16_CS
440         mov     dx, (AMD_PRIVATE_PARAMS PTR ss:[edi]).Gate16_SS
441
442         mov     eax, edi             ; Save edi in eax for after RM switch
443         mov     edi, esp             ; Save our current ESP for RM
444
445         movzx   ebx, dx
446         shl     ebx, 4
447         sub     esp, ebx
448
449 ;
450 ; We had been accessing the stack in PM32, we will now change to PM16 so we
451 ; will make the stack segment 64KB limit so SP needs to be fixed made PM16
452 ; compatible.
453 ;
454         mov     bx, AGESA_SELECTOR_DATA16
455         mov     ss, bx
456
457 ;
458 ; Save the RM segment and RM offset of the jump we will need to make in
459 ; order to enter RM so that code in this segment is relocatable.
460 ;
461 ; BEGIN --- Don't unbalance the stack --- BEGIN
462 ;
463         push    cx
464         pushw   OFFSET RMEntry
465
466         mov     ebx, CR0
467         and     bl, NOT 1
468         mov     CR0, ebx                ; CR0.PE cleared
469 ;
470 ; Far jump to clear segment descriptor cache and enter RM
471 ;
472         retf
473
474 RMEntry:
475 ;
476 ; We are in RM, setup RM stack
477 ;
478         movzx   ebx, dx               ; Get RM SS in ebx
479         shl     ebx, 4                  ; Get our stack top on entry in EBP to
480         sub     ebp, ebx                ; access our entry parameters
481         sub     eax, ebx                ; save copy of parameters address
482         mov     ss, dx                  ; Set stack segment
483 ;
484 ; We are going to figure out the address to use when we return
485 ; and have to go back into PM32 while we have access to it
486 ;
487         movzx   ebx, cx               ; Get original CS in ebx
488         shl     ebx, 4
489         add     ebx, OFFSET PM32Entry
490 ;
491 ; Now we put our data, func, block params into calling convention
492 ; for our hook
493 ;
494 ; ECX = Func
495 ; EDX = Data
496 ; ESI = config pointer
497 ;
498         mov     ecx, PARAM1             ; Func
499         mov     edx, PARAM2             ; Data
500         mov     esi, PARAM3             ; pointer
501
502         push    ebx                    ; Save PM32 mode switch address
503         push    edi                    ; Save PM32 stack pointer
504         pushf
505 ;
506 ; Get Router Function Address
507 ;
508         mov     edi, eax
509         mov     ax, (AMD_PRIVATE_PARAMS PTR ss:[edi]).Router_Seg
510         mov     fs, ax
511         mov     ax, (AMD_PRIVATE_PARAMS PTR ss:[edi]).Router_Off
512         mov     gs, ax
513
514         mov     eax, AGESA_UNSUPPORTED  ; Default return value
515 ;
516 ; If AMD_BRIDGE_32 EDX == 0 call oemCallout
517 ; otherwise call FAR PTR EDX
518 ;
519 ; Critical:
520 ;   sp+2 - EDI aka PM32 stack address
521 ;   sp+4 - address of PM32Entry in PM32
522 ;
523         mov     bx, fs
524         shl     ebx, 16
525         mov     bx, gs
526
527         .if (ebx == 0)
528             call        LocalOemCalloutRouter
529         .else
530 ;
531 ; Make far call to Router function
532 ;
533         push    cs
534         push    offset CalloutReturn
535         push    ebx
536         retf
537 CalloutReturn:
538     .endif
539 ;
540 ; Restore PM32 esp from RM stack
541 ;
542         popf
543         pop     edi                     ; Our PM32 stack pointer
544         pop     edx                     ; Our PM32 mode switch address
545
546         mov     ebx, CR0
547         or      bl, 1                   ; CR0.PE set
548         mov     CR0, ebx
549
550         mov     ebx, AGESA_SELECTOR_DATA32
551         pushd   AGESA_SELECTOR_CODE32 ; PM32 selector
552         push    edx                    ; PM32 entry point
553
554         DB      066h
555         retf                        ; Far jump to enter PM32
556
557 PM32Entry:
558 ;
559 ; END --- Don't unbalance the stack --- END
560 ; We are now PM32, so remember MASM is assembling in 16-bit again
561 ;
562         mov     ss, bx
563         mov     ds, bx
564         mov     es, bx
565         mov     fs, bx
566         mov     gs, bx
567
568         mov     sp, di
569         pop     di
570         pop     dx
571         pop     cx
572         pop     di
573         pop     si
574         pop     bx
575         pop     bp
576                             ; EXIT AMD_CALLOUT_16
577 ENDM