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