win32/Makefile: clean hello.exe on "make tidy"
[syslinux.git] / com32.inc
blobac5135938239b39bd7a64752c02bf1d3161c2e54
1 ;; -----------------------------------------------------------------------
2 ;;
3 ;;   Copyright 1994-2008 H. Peter Anvin - All Rights Reserved
4 ;;
5 ;;   This program is free software; you can redistribute it and/or modify
6 ;;   it under the terms of the GNU General Public License as published by
7 ;;   the Free Software Foundation, Inc., 53 Temple Place Ste 330,
8 ;;   Boston MA 02111-1307, USA; either version 2 of the License, or
9 ;;   (at your option) any later version; incorporated herein by reference.
11 ;; -----------------------------------------------------------------------
14 ;; com32.inc
16 ;; Common code for running a COM32 image
20 ; Load a COM32 image.  A COM32 image is the 32-bit analogue to a DOS
21 ; .com file.  A COM32 image is loaded at address 0x101000, with %esp
22 ; set to the high end of usable memory.
24 ; A COM32 image should begin with the magic bytes:
25 ; B8 FF 4C CD 21, which is "mov eax,0x21cd4cff" in 32-bit mode and
26 ; "mov ax,0x4cff; int 0x21" in 16-bit mode.  This will abort the
27 ; program with an error if run in 16-bit mode.
29 pm_idt:         equ 0x100000
30 pm_entry:       equ 0x101000
32                 bits 16
33                 section .data
34                 align 2, db 0
35 com32_pmidt:
36                 dw 8*256                ; Limit
37                 dd pm_idt               ; Address
39 com32_rmidt:
40                 dw 0ffffh               ; Limit
41                 dd 0                    ; Address
43                 section .text
44 is_com32_image:
45                 push si                 ; Save file handle
46                 push dx                 ; File length held in DX:AX
47                 push ax
49                 call make_plain_cmdline
50                 ; Copy the command line into the low cmdline buffer
51                 mov ax,real_mode_seg
52                 mov fs,ax
53                 mov si,cmd_line_here
54                 mov di,command_line
55                 mov cx,[CmdLinePtr]
56                 inc cx                  ; Include final null
57                 sub cx,si
58                 fs rep movsb
60                 call comboot_setup_api  ; Set up the COMBOOT-style API
62                 mov edi,pm_entry        ; Load address
63                 pop eax                 ; File length
64                 pop si                  ; File handle
65                 xor dx,dx               ; No padding
66                 mov bx,abort_check      ; Don't print dots, but allow abort
67                 call load_high
69 com32_start:
70                 mov ebx,com32_call_start        ; Where to go in PM
72 com32_enter_pm:
73                 cli
74                 mov ax,cs
75                 mov ds,ax
76                 mov [RealModeSSSP],sp
77                 mov [RealModeSSSP+2],ss
78                 cld
79                 call a20_test
80                 jnz .a20ok
81                 call enable_a20
83 .a20ok:
84                 mov byte [bcopy_gdt.TSS+5],89h  ; Mark TSS unbusy
86                 lgdt [bcopy_gdt]        ; We can use the same GDT just fine
87                 lidt [com32_pmidt]      ; Set up the IDT
88                 mov eax,cr0
89                 or al,1
90                 mov cr0,eax             ; Enter protected mode
91                 jmp PM_CS32:.in_pm
93                 bits 32
94 .in_pm:
95                 xor eax,eax             ; Available for future use...
96                 mov fs,eax
97                 mov gs,eax
98                 lldt ax
100                 mov al,PM_DS32          ; Set up data segments
101                 mov es,eax
102                 mov ds,eax
103                 mov ss,eax
105                 mov al,PM_TSS           ; Be nice to Intel's VT by
106                 ltr ax                  ; giving it a valid TR
108                 mov esp,[PMESP]         ; Load protmode %esp if available
109                 jmp ebx                 ; Go to where we need to go
112 ; This is invoked right before the actually starting the COM32
113 ; progam, in 32-bit mode...
115 com32_call_start:
116                 ;
117                 ; Point the stack to the end of (permitted) high memory
118                 ;
119                 mov esp,[word HighMemRsvd]
120                 xor sp,sp               ; Align to a 64K boundary
122                 ;
123                 ; Set up the protmode IDT and the interrupt jump buffers
124                 ; We set these up in the system area at 0x100000,
125                 ; but we could also put them beyond the stack.
126                 ;
127                 mov edi,pm_idt
129                 ; Form an interrupt gate descriptor
130                 mov eax,0x00200000+((pm_idt+8*256)&0x0000ffff)
131                 mov ebx,0x0000ee00+((pm_idt+8*256)&0xffff0000)
132                 xor ecx,ecx
133                 inc ch                          ; ecx <- 256
135                 push ecx
136 .make_idt:
137                 stosd
138                 add eax,8
139                 xchg eax,ebx
140                 stosd
141                 xchg eax,ebx
142                 loop .make_idt
144                 pop ecx
146                 ; Each entry in the interrupt jump buffer contains
147                 ; the following instructions:
148                 ;
149                 ; 00000000 60                pushad
150                 ; 00000001 B0xx              mov al,<interrupt#>
151                 ; 00000003 E9xxxxxxxx        jmp com32_handle_interrupt
153                 mov eax,0e900b060h
154                 mov ebx,com32_handle_interrupt-(pm_idt+8*256+8)
156 .make_ijb:
157                 stosd
158                 sub [edi-2],cl                  ; Interrupt #
159                 xchg eax,ebx
160                 stosd
161                 sub eax,8
162                 xchg eax,ebx
163                 loop .make_ijb
165                 ; Now everything is set up for interrupts...
167                 push dword com32_cfarcall       ; Cfarcall entry point
168                 push dword com32_farcall        ; Farcall entry point
169                 push dword (1 << 16)            ; 64K bounce buffer
170                 push dword (comboot_seg << 4)   ; Bounce buffer address
171                 push dword com32_intcall        ; Intcall entry point
172                 push dword command_line         ; Command line pointer
173                 push dword 6                    ; Argument count
174                 sti                             ; Interrupts OK now
175                 call pm_entry                   ; Run the program...
176                 ; ... on return, fall through to com32_exit ...
178 com32_exit:
179                 mov bx,com32_done       ; Return to command loop
181 com32_enter_rm:
182                 cli
183                 cld
184                 mov [PMESP],esp         ; Save exit %esp
185                 xor esp,esp             ; Make sure the high bits are zero
186                 jmp PM_CS16:.in_pm16    ; Return to 16-bit mode first
188                 bits 16
189 .in_pm16:
190                 mov ax,PM_DS16_RM       ; Real-mode-like segment
191                 mov es,ax
192                 mov ds,ax
193                 mov ss,ax
194                 mov fs,ax
195                 mov gs,ax
197                 lidt [com32_rmidt]      ; Real-mode IDT (rm needs no GDT)
198                 mov eax,cr0
199                 and al,~1
200                 mov cr0,eax
201                 jmp 0:.in_rm
203 .in_rm:                                 ; Back in real mode
204                 mov ax,cs               ; Set up sane segments
205                 mov ds,ax
206                 mov es,ax
207                 mov fs,ax
208                 mov gs,ax
209                 lss sp,[RealModeSSSP]   ; Restore stack
210                 jmp bx                  ; Go to whereever we need to go...
212 com32_done:
213 %if DISABLE_A20
214                 call disable_a20
215 %endif
216                 sti
217                 jmp enter_command
220 ; 16-bit support code
222                 bits 16
225 ; 16-bit interrupt-handling code
227 com32_int_rm:
228                 pushf                           ; Flags on stack
229                 push cs                         ; Return segment
230                 push word .cont                 ; Return address
231                 push dword edx                  ; Segment:offset of IVT entry
232                 retf                            ; Invoke IVT routine
233 .cont:          ; ... on resume ...
234                 mov ebx,com32_int_resume
235                 jmp com32_enter_pm              ; Go back to PM
238 ; 16-bit intcall/farcall handling code
240 com32_sys_rm:
241                 pop gs
242                 pop fs
243                 pop es
244                 pop ds
245                 popad
246                 popfd
247                 mov [cs:Com32SysSP],sp
248                 retf                            ; Invoke routine
249 .return:
250                 ; We clean up SP here because we don't know if the
251                 ; routine returned with RET, RETF or IRET
252                 mov sp,[cs:Com32SysSP]
253                 pushfd
254                 pushad
255                 push ds
256                 push es
257                 push fs
258                 push gs
259                 mov ebx,com32_syscall.resume
260                 jmp com32_enter_pm
263 ; 16-bit cfarcall handing code
265 com32_cfar_rm:
266                 retf
267 .return:
268                 mov sp,[cs:Com32SysSP]
269                 mov [cs:RealModeEAX],eax
270                 mov ebx,com32_cfarcall.resume
271                 jmp com32_enter_pm
274 ; 32-bit support code
276                 bits 32
279 ; This is invoked on getting an interrupt in protected mode.  At
280 ; this point, we need to context-switch to real mode and invoke
281 ; the interrupt routine.
283 ; When this gets invoked, the registers are saved on the stack and
284 ; AL contains the register number.
286 com32_handle_interrupt:
287                 movzx eax,al
288                 xor ebx,ebx             ; Actually makes the code smaller
289                 mov edx,[ebx+eax*4]     ; Get the segment:offset of the routine
290                 mov bx,com32_int_rm
291                 jmp com32_enter_rm      ; Go to real mode
293 com32_int_resume:
294                 popad
295                 iret
298 ; Intcall/farcall invocation.  We manifest a structure on the real-mode stack,
299 ; containing the com32sys_t structure from <com32.h> as well as
300 ; the following entries (from low to high address):
301 ; - Target offset
302 ; - Target segment
303 ; - Return offset
304 ; - Return segment (== real mode cs == 0)
305 ; - Return flags
307 com32_farcall:
308                 pushfd                          ; Save IF among other things...
309                 pushad                          ; We only need to save some, but...
311                 mov eax,[esp+10*4]              ; CS:IP
312                 jmp com32_syscall
315 com32_intcall:
316                 pushfd                          ; Save IF among other things...
317                 pushad                          ; We only need to save some, but...
319                 movzx eax,byte [esp+10*4]       ; INT number
320                 mov eax,[eax*4]                 ; Get CS:IP from low memory
322 com32_syscall:
323                 cld
325                 movzx edi,word [word RealModeSSSP]
326                 movzx ebx,word [word RealModeSSSP+2]
327                 sub edi,54              ; Allocate 54 bytes
328                 mov [word RealModeSSSP],di
329                 shl ebx,4
330                 add edi,ebx             ; Create linear address
332                 mov esi,[esp+11*4]      ; Source regs
333                 xor ecx,ecx
334                 mov cl,11               ; 44 bytes to copy
335                 rep movsd
337                 ; EAX is already set up to be CS:IP
338                 stosd                   ; Save in stack frame
339                 mov eax,com32_sys_rm.return     ; Return seg:offs
340                 stosd                   ; Save in stack frame
341                 mov eax,[edi-12]        ; Return flags
342                 and eax,0x200cd7        ; Mask (potentially) unsafe flags
343                 mov [edi-12],eax        ; Primary flags entry
344                 stosw                   ; Return flags
346                 mov bx,com32_sys_rm
347                 jmp com32_enter_rm      ; Go to real mode
349                 ; On return, the 44-byte return structure is on the
350                 ; real-mode stack, plus the 10 additional bytes used
351                 ; by the target address (see above.)
352 .resume:
353                 movzx esi,word [word RealModeSSSP]
354                 movzx eax,word [word RealModeSSSP+2]
355                 mov edi,[esp+12*4]      ; Dest regs
356                 shl eax,4
357                 add esi,eax             ; Create linear address
358                 and edi,edi             ; NULL pointer?
359                 jnz .do_copy
360 .no_copy:       mov edi,esi             ; Do a dummy copy-to-self
361 .do_copy:       xor ecx,ecx
362                 mov cl,11               ; 44 bytes
363                 rep movsd               ; Copy register block
365                 add dword [word RealModeSSSP],54        ; Remove from stack
367                 popad
368                 popfd
369                 ret                     ; Return to 32-bit program
372 ; Cfarcall invocation.  We copy the stack frame to the real-mode stack,
373 ; followed by the return CS:IP and the CS:IP of the target function.
375 com32_cfarcall:
376                 pushfd
377                 pushad
379                 cld
380                 mov ecx,[esp+12*4]              ; Size of stack frame
382                 movzx edi,word [word RealModeSSSP]
383                 movzx ebx,word [word RealModeSSSP+2]
384                 mov [word Com32SysSP],di
385                 sub edi,ecx             ; Allocate space for stack frame
386                 and edi,~3              ; Round
387                 sub edi,4*2             ; Return pointer, return value
388                 mov [word RealModeSSSP],di
389                 shl ebx,4
390                 add edi,ebx             ; Create linear address
392                 mov eax,[esp+10*4]      ; CS:IP
393                 stosd                   ; Save to stack frame
394                 mov eax,com32_cfar_rm.return    ; Return seg:off
395                 stosd
396                 mov esi,[esp+11*4]      ; Stack frame
397                 mov eax,ecx             ; Copy the stack frame
398                 shr ecx,2
399                 rep movsd
400                 mov ecx,eax
401                 and ecx,3
402                 rep movsb
404                 mov bx,com32_cfar_rm
405                 jmp com32_enter_rm
407 .resume:
408                 popad
409                 mov eax,[word RealModeEAX]
410                 popfd
411                 ret
413                 bits 16
415                 section .bss1
416                 alignb 4
417 RealModeSSSP    resd 1                  ; Real-mode SS:SP
418 RealModeEAX     resd 1                  ; Real mode EAX
419 PMESP           resd 1                  ; Protected-mode ESP
420 Com32SysSP      resw 1                  ; SP saved during COM32 syscall
422                 section .text