Revert "memdisk: memdisk16.asm needs %ifndef DEPEND around %include"
[profile/ivi/syslinux.git] / memdisk / memdisk16.asm
1 ;; -*- fundamental -*-
2 ;; -----------------------------------------------------------------------
3 ;;
4 ;;   Copyright 1994-2008 H. Peter Anvin - All Rights Reserved
5 ;;
6 ;;   This program is free software; you can redistribute it and/or modify
7 ;;   it under the terms of the GNU General Public License as published by
8 ;;   the Free Software Foundation, Inc., 53 Temple Place Ste 330,
9 ;;   Boston MA 02111-1307, USA; either version 2 of the License, or
10 ;;   (at your option) any later version; incorporated herein by reference.
11 ;;
12 ;; -----------------------------------------------------------------------
13
14 ;;
15 ;; init16.asm
16 ;;
17 ;; Routine to initialize and to trampoline into 32-bit
18 ;; protected memory.  This code is derived from bcopy32.inc and
19 ;; com32.inc in the main SYSLINUX distribution.
20 ;;
21
22 %include '../version.gen'
23
24 MY_CS           equ 0x0800              ; Segment address to use
25 CS_BASE         equ (MY_CS << 4)        ; Corresponding address
26
27 ; Low memory bounce buffer
28 BOUNCE_SEG      equ (MY_CS+0x1000)
29
30 %define DO_WBINVD 0
31
32 %define STACK_HEAP_SIZE (128*1024)
33
34                 section .rodata align=16
35                 section .data   align=16
36                 section .bss    align=16
37
38 ;; -----------------------------------------------------------------------
39 ;;  Kernel image header
40 ;; -----------------------------------------------------------------------
41
42                 section .text           ; Must be first in image
43                 bits 16
44
45 cmdline         times 497 db 0          ; We put the command line here
46 setup_sects     db 0
47 root_flags      dw 0
48 syssize         dw 0
49 swap_dev        dw 0
50 ram_size        dw 0
51 vid_mode        dw 0
52 root_dev        dw 0
53 boot_flag       dw 0xAA55
54
55 _start:         jmp short start
56
57                 db "HdrS"               ; Header signature
58                 dw 0x0203               ; Header version number
59
60 realmode_swtch  dw 0, 0                 ; default_switch, SETUPSEG
61 start_sys_seg   dw 0x1000               ; obsolete
62 version_ptr     dw memdisk_version-0x200        ; version string ptr
63 type_of_loader  db 0                    ; Filled in by boot loader
64 loadflags       db 1                    ; Please load high
65 setup_move_size dw 0                    ; Unused
66 code32_start    dd 0x100000             ; 32-bit start address
67 ramdisk_image   dd 0                    ; Loaded ramdisk image address
68 ramdisk_size    dd 0                    ; Size of loaded ramdisk
69 bootsect_kludge dw 0, 0
70 heap_end_ptr    dw 0
71 pad1            dw 0
72 cmd_line_ptr    dd 0                    ; Command line
73 ramdisk_max     dd 0xffffffff           ; Highest allowed ramdisk address
74
75 ;
76 ; These fields aren't real setup fields, they're poked in by the
77 ; 32-bit code.
78 ;
79 b_esdi          dd 0                    ; ES:DI for boot sector invocation
80 b_edx           dd 0                    ; EDX for boot sector invocation
81
82                 section .rodata
83 memdisk_version:
84                 db "MEMDISK ", VERSION_STR, " ", DATE, 0
85
86 ;; -----------------------------------------------------------------------
87 ;;  End kernel image header
88 ;; -----------------------------------------------------------------------
89
90 ;
91 ; Move ourselves down into memory to reduce the risk of conflicts;
92 ; then canonicalize CS to match the other segments.
93 ;
94                 section .text
95                 bits 16
96 start:
97                 mov ax,MY_CS
98                 mov es,ax
99                 movzx cx,byte [setup_sects]
100                 inc cx                  ; Add one for the boot sector
101                 shl cx,7                ; Convert to dwords
102                 xor si,si
103                 xor di,di
104                 mov fs,si               ; fs <- 0
105                 cld
106                 rep movsd
107                 mov ds,ax
108                 mov ss,ax
109                 xor esp,esp             ; Stack at top of 64K segment
110                 jmp MY_CS:.next
111 .next:
112
113 ;
114 ; Copy the command line, if there is one
115 ;
116 copy_cmdline:
117                 xor di,di               ; Bottom of our own segment (= "boot sector")
118                 mov eax,[cmd_line_ptr]
119                 and eax,eax
120                 jz .endcmd              ; No command line
121                 mov si,ax
122                 shr eax,4               ; Convert to segment
123                 and si,0x000F           ; Starting offset only
124                 mov gs,ax
125                 mov cx,496              ; Max number of bytes
126 .copycmd:
127                 gs lodsb
128                 and al,al
129                 jz .endcmd
130                 stosb
131                 loop .copycmd
132 .endcmd:
133                 xor al,al
134                 stosb
135
136 ;
137 ; Now jump to 32-bit code
138 ;
139                 sti
140                 call init32
141 ;
142 ; When init32 returns, we have been set up, the new boot sector loaded,
143 ; and we should go and and run the newly loaded boot sector.
144 ;
145 ; The setup function will have poked values into the setup area.
146 ;
147                 movzx edi,word [cs:b_esdi]
148                 mov es,word [cs:b_esdi+2]
149                 mov edx,[cs:b_edx]
150
151                 cli
152                 xor esi,esi             ; No partition table involved
153                 mov ds,si               ; Make all the segments consistent
154                 mov fs,si
155                 mov gs,si
156                 mov ss,si
157                 mov esp,0x7C00          ; Good place for SP to start out
158                 call 0:0x7C00
159                 int 18h                 ; A far return -> INT 18h
160
161 ;
162 ; We enter protected mode, set up a flat 32-bit environment, run rep movsd
163 ; and then exit.  IMPORTANT: This code assumes cs == MY_CS.
164 ;
165 ; This code is probably excessively anal-retentive in its handling of
166 ; segments, but this stuff is painful enough as it is without having to rely
167 ; on everything happening "as it ought to."
168 ;
169                 section .rodata
170
171         ; desc base, limit, flags
172 %macro  desc 3
173         dd (%2 & 0xffff) | ((%1 & 0xffff) << 16)
174         dd (%1 & 0xff000000) | (%2 & 0xf0000) | ((%3 & 0xf0ff) << 8) | ((%1 & 0x00ff0000) >> 16)
175 %endmacro
176
177                 align 8, db 0
178 call32_gdt:     dw call32_gdt_size-1    ; Null descriptor - contains GDT
179 .adj1:          dd call32_gdt+CS_BASE   ; pointer for LGDT instruction
180                 dw 0
181
182                 ; 0008: Code segment, use16, readable, dpl 0, base CS_BASE, 64K
183                 desc CS_BASE, 0xffff, 0x009b
184
185                 ; 0010: Data segment, use16, read/write, dpl 0, base CS_BASE, 64K
186                 desc CS_BASE, 0xffff, 0x0093
187
188                 ; 0018: Data segment, use16, read/write, dpl 0, base 0, 4G
189                 desc 0, 0xfffff, 0x809b
190
191                 ; 0020: Code segment, use32, read/write, dpl 0, base 0, 4G
192                 desc 0, 0xfffff, 0xc09b
193
194                 ; 0028: Data segment, use32, read/write, dpl 0, base 0, 4G
195                 desc 0, 0xfffff, 0xc093
196
197 call32_gdt_size:        equ $-call32_gdt
198
199 err_a20:        db 'ERROR: A20 gate not responding!',13,10,0
200
201                 section .bss
202                 alignb 4
203 SavedSSSP       resd 1                  ; Place to save SS:SP
204 Return          resd 1                  ; Return value
205 A20Test         resw 1                  ; Space to test A20
206 A20Tries        resb 1
207
208                 section .data
209                 alignb 4
210 Target          dd 0                    ; Target address
211 Target_Seg      dw 20h                  ; Target CS
212
213 A20Type         dw 0                    ; Default = unknown
214
215                 section .text
216                 bits 16
217 ;
218 ; Routines to enable and disable (yuck) A20.  These routines are gathered
219 ; from tips from a couple of sources, including the Linux kernel and
220 ; http://www.x86.org/.  The need for the delay to be as large as given here
221 ; is indicated by Donnie Barnes of RedHat, the problematic system being an
222 ; IBM ThinkPad 760EL.
223 ;
224 ; We typically toggle A20 twice for every 64K transferred.
225 ;
226 %define io_delay        call _io_delay
227 %define IO_DELAY_PORT   80h             ; Invalid port (we hope!)
228 %define disable_wait    32              ; How long to wait for a disable
229
230 %define A20_DUNNO       0               ; A20 type unknown
231 %define A20_NONE        1               ; A20 always on?
232 %define A20_BIOS        2               ; A20 BIOS enable
233 %define A20_KBC         3               ; A20 through KBC
234 %define A20_FAST        4               ; A20 through port 92h
235
236                 align 2, db 0
237 A20List         dw a20_dunno, a20_none, a20_bios, a20_kbc, a20_fast
238 A20DList        dw a20d_dunno, a20d_none, a20d_bios, a20d_kbc, a20d_fast
239 a20_adjust_cnt  equ ($-A20List)/2
240
241 slow_out:       out dx, al              ; Fall through
242
243 _io_delay:      out IO_DELAY_PORT,al
244                 out IO_DELAY_PORT,al
245                 ret
246
247 enable_a20:
248                 pushad
249                 mov byte [A20Tries],255 ; Times to try to make this work
250
251 try_enable_a20:
252
253 ;
254 ; Flush the caches
255 ;
256 %if DO_WBINVD
257                 call try_wbinvd
258 %endif
259
260 ;
261 ; If the A20 type is known, jump straight to type
262 ;
263                 mov bp,[A20Type]
264                 add bp,bp                       ; Convert to word offset
265 .adj4:          jmp word [bp+A20List]
266
267 ;
268 ; First, see if we are on a system with no A20 gate
269 ;
270 a20_dunno:
271 a20_none:
272                 mov byte [A20Type], A20_NONE
273                 call a20_test
274                 jnz a20_done
275
276 ;
277 ; Next, try the BIOS (INT 15h AX=2401h)
278 ;
279 a20_bios:
280                 mov byte [A20Type], A20_BIOS
281                 mov ax,2401h
282                 pushf                           ; Some BIOSes muck with IF
283                 int 15h
284                 popf
285
286                 call a20_test
287                 jnz a20_done
288
289 ;
290 ; Enable the keyboard controller A20 gate
291 ;
292 a20_kbc:
293                 mov dl, 1                       ; Allow early exit
294                 call empty_8042
295                 jnz a20_done                    ; A20 live, no need to use KBC
296
297                 mov byte [A20Type], A20_KBC     ; Starting KBC command sequence
298
299                 mov al,0D1h                     ; Write output port
300                 out 064h, al
301                 call empty_8042_uncond
302
303                 mov al,0DFh                     ; A20 on
304                 out 060h, al
305                 call empty_8042_uncond
306
307                 ; Apparently the UHCI spec assumes that A20 toggle
308                 ; ends with a null command (assumed to be for sychronization?)
309                 ; Put it here to see if it helps anything...
310                 mov al,0FFh                     ; Null command
311                 out 064h, al
312                 call empty_8042_uncond
313
314                 ; Verify that A20 actually is enabled.  Do that by
315                 ; observing a word in low memory and the same word in
316                 ; the HMA until they are no longer coherent.  Note that
317                 ; we don't do the same check in the disable case, because
318                 ; we don't want to *require* A20 masking (SYSLINUX should
319                 ; work fine without it, if the BIOS does.)
320 .kbc_wait:      push cx
321                 xor cx,cx
322 .kbc_wait_loop:
323                 call a20_test
324                 jnz a20_done_pop
325                 loop .kbc_wait_loop
326
327                 pop cx
328 ;
329 ; Running out of options here.  Final attempt: enable the "fast A20 gate"
330 ;
331 a20_fast:
332                 mov byte [A20Type], A20_FAST    ; Haven't used the KBC yet
333                 in al, 092h
334                 or al,02h
335                 and al,~01h                     ; Don't accidentally reset the machine!
336                 out 092h, al
337
338 .fast_wait:     push cx
339                 xor cx,cx
340 .fast_wait_loop:
341                 call a20_test
342                 jnz a20_done_pop
343                 loop .fast_wait_loop
344
345                 pop cx
346
347 ;
348 ; Oh bugger.  A20 is not responding.  Try frobbing it again; eventually give up
349 ; and report failure to the user.
350 ;
351
352                 dec byte [A20Tries]
353                 jnz try_enable_a20
354
355
356                 ; Error message time
357                 mov si,err_a20
358 print_err:
359                 lodsb
360                 and al,al
361                 jz die
362                 mov bx,7
363                 mov ah,0xe
364                 int 10h
365                 jmp print_err
366
367
368 die:
369                 sti
370 .hlt:           hlt
371                 jmp short .hlt
372
373 ;
374 ; A20 unmasked, proceed...
375 ;
376 a20_done_pop:   pop cx
377 a20_done:       popad
378                 ret
379
380 ;
381 ; This routine tests if A20 is enabled (ZF = 0).  This routine
382 ; must not destroy any register contents.
383 ;
384 a20_test:
385                 push es
386                 push cx
387                 push ax
388                 mov cx,0FFFFh           ; HMA = segment 0FFFFh
389                 mov es,cx
390                 mov cx,32               ; Loop count
391                 mov ax,[A20Test]
392 .a20_wait:      inc ax
393                 mov [A20Test],ax
394                 io_delay                ; Serialize, and fix delay
395                 cmp ax,[es:A20Test+CS_BASE+10h]
396                 loopz .a20_wait
397 .a20_done:      pop ax
398                 pop cx
399                 pop es
400                 ret
401
402 disable_a20:
403                 pushad
404 ;
405 ; Flush the caches
406 ;
407 %if DO_WBINVD
408                 call try_wbinvd
409 %endif
410
411                 mov bp,[A20Type]
412                 add bp,bp                       ; Convert to word offset
413 .adj5:          jmp word [bp+A20DList]
414
415 a20d_bios:
416                 mov ax,2400h
417                 pushf                           ; Some BIOSes muck with IF
418                 int 15h
419                 popf
420                 jmp short a20d_snooze
421
422 ;
423 ; Disable the "fast A20 gate"
424 ;
425 a20d_fast:
426                 in al, 092h
427                 and al,~03h
428                 out 092h, al
429                 jmp short a20d_snooze
430
431 ;
432 ; Disable the keyboard controller A20 gate
433 ;
434 a20d_kbc:
435                 call empty_8042_uncond
436
437                 mov al,0D1h
438                 out 064h, al            ; Write output port
439                 call empty_8042_uncond
440
441                 mov al,0DDh             ; A20 off
442                 out 060h, al
443                 call empty_8042_uncond
444
445                 mov al,0FFh             ; Null command/synchronization
446                 out 064h, al
447                 call empty_8042_uncond
448
449                 ; Wait a bit for it to take effect
450 a20d_snooze:
451                 push cx
452                 mov cx, disable_wait
453 .delayloop:     call a20_test
454                 jz .disabled
455                 loop .delayloop
456 .disabled:      pop cx
457 a20d_dunno:
458 a20d_none:
459                 popad
460                 ret
461
462 ;
463 ; Routine to empty the 8042 KBC controller.  If dl != 0
464 ; then we will test A20 in the loop and exit if A20 is
465 ; suddenly enabled.
466 ;
467 empty_8042_uncond:
468                 xor dl,dl
469 empty_8042:
470                 call a20_test
471                 jz .a20_on
472                 and dl,dl
473                 jnz .done
474 .a20_on:        io_delay
475                 in al, 064h             ; Status port
476                 test al,1
477                 jz .no_output
478                 io_delay
479                 in al, 060h             ; Read input
480                 jmp short empty_8042
481 .no_output:
482                 test al,2
483                 jnz empty_8042
484                 io_delay
485 .done:          ret
486
487 ;
488 ; Execute a WBINVD instruction if possible on this CPU
489 ;
490 %if DO_WBINVD
491 try_wbinvd:
492                 wbinvd
493                 ret
494 %endif
495
496                 section .bss
497                 alignb 4
498 PMESP           resd 1                  ; Protected mode %esp
499
500                 section .idt nobits align=4096
501                 alignb 4096
502 pm_idt          resb 4096               ; Protected-mode IDT, followed by interrupt stubs
503
504
505
506
507 pm_entry:       equ 0x100000
508
509                 section .rodata
510                 align 4, db 0
511 call32_pmidt:
512                 dw 8*256                ; Limit
513                 dd pm_idt+CS_BASE       ; Address
514
515 call32_rmidt:
516                 dw 0ffffh               ; Limit
517                 dd 0                    ; Address
518
519                 section .text
520 ;
521 ; This is the main entrypoint in this function
522 ;
523 init32:
524                 mov ebx,call32_call_start+CS_BASE       ; Where to go in PM
525
526 call32_enter_pm:
527                 mov ax,cs
528                 mov ds,ax
529                 cli
530                 mov [SavedSSSP],sp
531                 mov [SavedSSSP+2],ss
532                 cld
533                 call a20_test
534                 jnz .a20ok
535                 call enable_a20
536
537 .a20ok:
538                 lgdt [call32_gdt]       ; Set up GDT
539                 lidt [call32_pmidt]     ; Set up the IDT
540                 mov eax,cr0
541                 or al,1
542                 mov cr0,eax             ; Enter protected mode
543                 jmp 20h:dword .in_pm+CS_BASE
544
545                 bits 32
546 .in_pm:
547                 xor eax,eax             ; Available for future use...
548                 mov fs,eax
549                 mov gs,eax
550
551                 mov al,28h              ; Set up data segments
552                 mov es,eax
553                 mov ds,eax
554                 mov ss,eax
555
556                 mov esp,[PMESP+CS_BASE] ; Load protmode %esp if available
557                 jmp ebx                 ; Go to where we need to go
558
559 ;
560 ; This is invoked before first dispatch of the 32-bit code, in 32-bit mode
561 ;
562 call32_call_start:
563                 ;
564                 ; Point the stack into low memory
565                 ; We have: this segment, bounce buffer, then stack+heap
566                 ;
567                 mov esp, CS_BASE + 0x20000 + STACK_HEAP_SIZE
568                 and esp, ~0xf
569
570                 ;
571                 ; Set up the protmode IDT and the interrupt jump buffers
572                 ;
573                 mov edi,pm_idt+CS_BASE
574
575                 ; Form an interrupt gate descriptor
576                 ; WARNING: This is broken if pm_idt crosses a 64K boundary;
577                 ; however, it can't because of the alignment constraints.
578                 mov ebx,pm_idt+CS_BASE+8*256
579                 mov eax,0x0020ee00
580                 xchg ax,bx
581                 xor ecx,ecx
582                 inc ch                          ; ecx <- 256
583
584                 push ecx
585 .make_idt:
586                 stosd
587                 add eax,8
588                 xchg eax,ebx
589                 stosd
590                 xchg eax,ebx
591                 loop .make_idt
592
593                 pop ecx
594
595                 ; Each entry in the interrupt jump buffer contains
596                 ; the following instructions:
597                 ;
598                 ; 00000000 60                pushad
599                 ; 00000001 B0xx              mov al,<interrupt#>
600                 ; 00000003 E9xxxxxxxx        jmp call32_handle_interrupt
601
602                 mov eax,0xe900b060
603                 mov ebx,call32_handle_interrupt+CS_BASE
604                 sub ebx,edi
605
606 .make_ijb:
607                 stosd
608                 sub [edi-2],cl                  ; Interrupt #
609                 xchg eax,ebx
610                 sub eax,8
611                 stosd
612                 xchg eax,ebx
613                 loop .make_ijb
614
615                 ; Now everything is set up for interrupts...
616
617                 push dword (BOUNCE_SEG << 4)    ; Bounce buffer address
618                 push dword call32_syscall+CS_BASE ; Syscall entry point
619                 sti                             ; Interrupts OK now
620                 call pm_entry-CS_BASE           ; Run the program...
621
622                 ; ... on return ...
623                 mov [Return+CS_BASE],eax
624
625                 ; ... fall through to call32_exit ...
626
627 call32_exit:
628                 mov bx,call32_done      ; Return to command loop
629
630 call32_enter_rm:
631                 cli
632                 cld
633                 mov [PMESP+CS_BASE],esp ; Save exit %esp
634                 xor esp,esp             ; Make sure the high bits are zero
635                 jmp 08h:.in_pm16        ; Return to 16-bit mode first
636
637                 bits 16
638 .in_pm16:
639                 mov ax,10h              ; Real-mode-like segment
640                 mov es,ax
641                 mov ds,ax
642                 mov ss,ax
643                 mov fs,ax
644                 mov gs,ax
645
646                 lidt [call32_rmidt]     ; Real-mode IDT (rm needs no GDT)
647                 mov eax,cr0
648                 and al,~1
649                 mov cr0,eax
650                 jmp MY_CS:.in_rm
651
652 .in_rm:                                 ; Back in real mode
653                 mov ax,cs               ; Set up sane segments
654                 mov ds,ax
655                 mov es,ax
656                 mov fs,ax
657                 mov gs,ax
658                 lss sp,[SavedSSSP]      ; Restore stack
659                 jmp bx                  ; Go to whereever we need to go...
660
661 call32_done:
662                 call disable_a20
663                 sti
664                 mov ax,[Return]
665                 ret
666
667 ;
668 ; 16-bit support code
669 ;
670                 bits 16
671
672 ;
673 ; 16-bit interrupt-handling code
674 ;
675 call32_int_rm:
676                 pushf                           ; Flags on stack
677                 push cs                         ; Return segment
678                 push word .cont                 ; Return address
679                 push dword edx                  ; Segment:offset of IVT entry
680                 retf                            ; Invoke IVT routine
681 .cont:          ; ... on resume ...
682                 mov ebx,call32_int_resume+CS_BASE
683                 jmp call32_enter_pm             ; Go back to PM
684
685 ;
686 ; 16-bit system call handling code
687 ;
688 call32_sys_rm:
689                 pop gs
690                 pop fs
691                 pop es
692                 pop ds
693                 popad
694                 popfd
695                 retf                            ; Invoke routine
696 .return:
697                 pushfd
698                 pushad
699                 push ds
700                 push es
701                 push fs
702                 push gs
703                 mov ebx,call32_sys_resume+CS_BASE
704                 jmp call32_enter_pm
705
706 ;
707 ; 32-bit support code
708 ;
709                 bits 32
710
711 ;
712 ; This is invoked on getting an interrupt in protected mode.  At
713 ; this point, we need to context-switch to real mode and invoke
714 ; the interrupt routine.
715 ;
716 ; When this gets invoked, the registers are saved on the stack and
717 ; AL contains the register number.
718 ;
719 call32_handle_interrupt:
720                 movzx eax,al
721                 xor ebx,ebx             ; Actually makes the code smaller
722                 mov edx,[ebx+eax*4]     ; Get the segment:offset of the routine
723                 mov bx,call32_int_rm
724                 jmp call32_enter_rm     ; Go to real mode
725
726 call32_int_resume:
727                 popad
728                 iret
729
730 ;
731 ; Syscall invocation.  We manifest a structure on the real-mode stack,
732 ; containing the call32sys_t structure from <call32.h> as well as
733 ; the following entries (from low to high address):
734 ; - Target offset
735 ; - Target segment
736 ; - Return offset
737 ; - Return segment (== real mode cs)
738 ; - Return flags
739 ;
740 call32_syscall:
741                 pushfd                  ; Save IF among other things...
742                 pushad                  ; We only need to save some, but...
743                 cld
744
745                 movzx edi,word [SavedSSSP+CS_BASE]
746                 movzx eax,word [SavedSSSP+CS_BASE+2]
747                 sub edi,54              ; Allocate 54 bytes
748                 mov [SavedSSSP+CS_BASE],di
749                 shl eax,4
750                 add edi,eax             ; Create linear address
751
752                 mov esi,[esp+11*4]      ; Source regs
753                 xor ecx,ecx
754                 mov cl,11               ; 44 bytes to copy
755                 rep movsd
756
757                 movzx eax,byte [esp+10*4] ; Interrupt number
758                 ; ecx == 0 here; adding it to the EA makes the
759                 ; encoding smaller
760                 mov eax,[ecx+eax*4]     ; Get IVT entry
761                 stosd                   ; Save in stack frame
762                 mov eax,call32_sys_rm.return + (MY_CS << 16) ; Return seg:offs
763                 stosd                   ; Save in stack frame
764                 mov eax,[edi-12]        ; Return flags
765                 and eax,0x200cd7        ; Mask (potentially) unsafe flags
766                 mov [edi-12],eax        ; Primary flags entry
767                 stosw                   ; Return flags
768
769                 mov bx,call32_sys_rm
770                 jmp call32_enter_rm     ; Go to real mode
771
772                 ; On return, the 44-byte return structure is on the
773                 ; real-mode stack.
774 call32_sys_resume:
775                 movzx esi,word [SavedSSSP+CS_BASE]
776                 movzx eax,word [SavedSSSP+CS_BASE+2]
777                 mov edi,[esp+12*4]      ; Dest regs
778                 shl eax,4
779                 add esi,eax             ; Create linear address
780                 and edi,edi             ; NULL pointer?
781                 jnz .do_copy
782 .no_copy:       mov edi,esi             ; Do a dummy copy-to-self
783 .do_copy:       xor ecx,ecx
784                 mov cl,11               ; 44 bytes
785                 rep movsd               ; Copy register block
786
787                 add dword [SavedSSSP+CS_BASE],44        ; Remove from stack
788
789                 popad
790                 popfd
791                 ret                     ; Return to 32-bit program