Magellan Linux

Annotation of /trunk/mkinitrd-magellan/isolinux/com32.inc

Parent Directory Parent Directory | Revision Log Revision Log


Revision 1133 - (hide annotations) (download)
Thu Aug 19 09:50:43 2010 UTC (13 years, 8 months ago) by niro
File size: 10096 byte(s)
-updated to isolinux-3.86
1 niro 532 ;; -----------------------------------------------------------------------
2     ;;
3 niro 1133 ;; Copyright 1994-2008 H. Peter Anvin - All Rights Reserved
4     ;;
5 niro 532 ;; 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.
10     ;;
11     ;; -----------------------------------------------------------------------
12    
13     ;;
14     ;; com32.inc
15     ;;
16     ;; Common code for running a COM32 image
17     ;;
18    
19     ;
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.
23     ;
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.
28     ;
29    
30 niro 1133 ; We need to make this a proper section rather
31     ; than using absolute numbers, in order to work
32     ; around a bug in GNU ld 2.17, which is still in
33     ; use as of this writing in the form of Debian
34     ; 4.0 (etch).
35     bits 32
36     section .com32 exec write nobits align=16
37     pm_idt equ 0x100000 ; Needs to be absolute...
38     resb 4096
39     pm_entry: ; Needs to not be...
40    
41 niro 532 bits 16
42     section .data
43 niro 1133 alignz 2
44 niro 532 com32_pmidt:
45     dw 8*256 ; Limit
46     dd pm_idt ; Address
47    
48     com32_rmidt:
49     dw 0ffffh ; Limit
50     dd 0 ; Address
51    
52     section .text
53     is_com32_image:
54     push si ; Save file handle
55 niro 1133 push eax ; Save file length
56 niro 532
57     call make_plain_cmdline
58     ; Copy the command line into the low cmdline buffer
59     mov ax,real_mode_seg
60     mov fs,ax
61     mov si,cmd_line_here
62     mov di,command_line
63     mov cx,[CmdLinePtr]
64     inc cx ; Include final null
65     sub cx,si
66     fs rep movsb
67    
68 niro 1133 mov si,KernelCName
69     mov di,Com32Name
70     call strcpy
71    
72 niro 532 call comboot_setup_api ; Set up the COMBOOT-style API
73    
74     mov edi,pm_entry ; Load address
75     pop eax ; File length
76     pop si ; File handle
77     xor dx,dx ; No padding
78 niro 1133 mov bx,abort_check ; Don't print dots, but allow abort
79 niro 532 call load_high
80    
81     com32_start:
82     mov ebx,com32_call_start ; Where to go in PM
83    
84     com32_enter_pm:
85     cli
86     mov ax,cs
87     mov ds,ax
88 niro 1133 mov [RealModeSSSP],sp
89     mov [RealModeSSSP+2],ss
90 niro 532 cld
91     call a20_test
92     jnz .a20ok
93     call enable_a20
94    
95     .a20ok:
96 niro 1133 mov byte [bcopy_gdt.TSS+5],89h ; Mark TSS unbusy
97    
98 niro 532 lgdt [bcopy_gdt] ; We can use the same GDT just fine
99     lidt [com32_pmidt] ; Set up the IDT
100     mov eax,cr0
101     or al,1
102     mov cr0,eax ; Enter protected mode
103 niro 1133 jmp PM_CS32:.in_pm
104    
105 niro 532 bits 32
106     .in_pm:
107     xor eax,eax ; Available for future use...
108     mov fs,eax
109     mov gs,eax
110 niro 1133 lldt ax
111 niro 532
112 niro 1133 mov al,PM_DS32 ; Set up data segments
113 niro 532 mov es,eax
114     mov ds,eax
115     mov ss,eax
116    
117 niro 1133 mov al,PM_TSS ; Be nice to Intel's VT by
118     ltr ax ; giving it a valid TR
119    
120 niro 532 mov esp,[PMESP] ; Load protmode %esp if available
121     jmp ebx ; Go to where we need to go
122    
123     ;
124     ; This is invoked right before the actually starting the COM32
125     ; progam, in 32-bit mode...
126     ;
127     com32_call_start:
128     ;
129 niro 1133 ; Point the stack to the end of (permitted) high memory
130 niro 532 ;
131 niro 1133 mov esp,[word HighMemRsvd]
132     xor sp,sp ; Align to a 64K boundary
133 niro 532
134     ;
135     ; Set up the protmode IDT and the interrupt jump buffers
136     ; We set these up in the system area at 0x100000,
137     ; but we could also put them beyond the stack.
138     ;
139     mov edi,pm_idt
140    
141     ; Form an interrupt gate descriptor
142     mov eax,0x00200000+((pm_idt+8*256)&0x0000ffff)
143     mov ebx,0x0000ee00+((pm_idt+8*256)&0xffff0000)
144     xor ecx,ecx
145     inc ch ; ecx <- 256
146    
147     push ecx
148     .make_idt:
149     stosd
150     add eax,8
151     xchg eax,ebx
152     stosd
153     xchg eax,ebx
154     loop .make_idt
155    
156     pop ecx
157    
158     ; Each entry in the interrupt jump buffer contains
159     ; the following instructions:
160     ;
161     ; 00000000 60 pushad
162     ; 00000001 B0xx mov al,<interrupt#>
163     ; 00000003 E9xxxxxxxx jmp com32_handle_interrupt
164    
165     mov eax,0e900b060h
166     mov ebx,com32_handle_interrupt-(pm_idt+8*256+8)
167    
168     .make_ijb:
169     stosd
170     sub [edi-2],cl ; Interrupt #
171     xchg eax,ebx
172     stosd
173     sub eax,8
174     xchg eax,ebx
175     loop .make_ijb
176    
177     ; Now everything is set up for interrupts...
178    
179 niro 1133 push dword Com32Name ; Module filename
180     push dword [HighMemSize] ; Memory managed by Syslinux
181     push dword com32_cfarcall ; Cfarcall entry point
182 niro 532 push dword com32_farcall ; Farcall entry point
183     push dword (1 << 16) ; 64K bounce buffer
184 niro 1133 push dword (xfer_buf_seg << 4) ; Bounce buffer address
185 niro 532 push dword com32_intcall ; Intcall entry point
186     push dword command_line ; Command line pointer
187 niro 1133 push dword 8 ; Argument count
188 niro 532 sti ; Interrupts OK now
189     call pm_entry ; Run the program...
190     ; ... on return, fall through to com32_exit ...
191    
192     com32_exit:
193     mov bx,com32_done ; Return to command loop
194    
195     com32_enter_rm:
196     cli
197     cld
198     mov [PMESP],esp ; Save exit %esp
199     xor esp,esp ; Make sure the high bits are zero
200 niro 1133 jmp PM_CS16:.in_pm16 ; Return to 16-bit mode first
201 niro 532
202     bits 16
203     .in_pm16:
204 niro 1133 mov ax,PM_DS16 ; Real-mode-like segment
205 niro 532 mov es,ax
206     mov ds,ax
207     mov ss,ax
208     mov fs,ax
209     mov gs,ax
210    
211     lidt [com32_rmidt] ; Real-mode IDT (rm needs no GDT)
212     mov eax,cr0
213     and al,~1
214     mov cr0,eax
215     jmp 0:.in_rm
216    
217     .in_rm: ; Back in real mode
218     mov ax,cs ; Set up sane segments
219     mov ds,ax
220     mov es,ax
221     mov fs,ax
222     mov gs,ax
223 niro 1133 lss sp,[RealModeSSSP] ; Restore stack
224 niro 532 jmp bx ; Go to whereever we need to go...
225    
226     com32_done:
227     sti
228     jmp enter_command
229    
230     ;
231     ; 16-bit support code
232     ;
233     bits 16
234    
235     ;
236     ; 16-bit interrupt-handling code
237     ;
238     com32_int_rm:
239     pushf ; Flags on stack
240     push cs ; Return segment
241     push word .cont ; Return address
242     push dword edx ; Segment:offset of IVT entry
243     retf ; Invoke IVT routine
244     .cont: ; ... on resume ...
245     mov ebx,com32_int_resume
246     jmp com32_enter_pm ; Go back to PM
247    
248     ;
249 niro 1133 ; 16-bit intcall/farcall handling code
250 niro 532 ;
251     com32_sys_rm:
252     pop gs
253     pop fs
254     pop es
255     pop ds
256     popad
257     popfd
258     mov [cs:Com32SysSP],sp
259     retf ; Invoke routine
260     .return:
261     ; We clean up SP here because we don't know if the
262     ; routine returned with RET, RETF or IRET
263     mov sp,[cs:Com32SysSP]
264     pushfd
265     pushad
266     push ds
267     push es
268     push fs
269     push gs
270 niro 1133 mov ebx,com32_syscall.resume
271 niro 532 jmp com32_enter_pm
272    
273     ;
274 niro 1133 ; 16-bit cfarcall handing code
275     ;
276     com32_cfar_rm:
277     retf
278     .return:
279     mov sp,[cs:Com32SysSP]
280     mov [cs:RealModeEAX],eax
281     mov ebx,com32_cfarcall.resume
282     jmp com32_enter_pm
283    
284     ;
285 niro 532 ; 32-bit support code
286     ;
287     bits 32
288    
289     ;
290     ; This is invoked on getting an interrupt in protected mode. At
291     ; this point, we need to context-switch to real mode and invoke
292     ; the interrupt routine.
293     ;
294     ; When this gets invoked, the registers are saved on the stack and
295     ; AL contains the register number.
296     ;
297     com32_handle_interrupt:
298     movzx eax,al
299     xor ebx,ebx ; Actually makes the code smaller
300     mov edx,[ebx+eax*4] ; Get the segment:offset of the routine
301     mov bx,com32_int_rm
302     jmp com32_enter_rm ; Go to real mode
303    
304     com32_int_resume:
305     popad
306     iret
307    
308     ;
309     ; Intcall/farcall invocation. We manifest a structure on the real-mode stack,
310     ; containing the com32sys_t structure from <com32.h> as well as
311     ; the following entries (from low to high address):
312     ; - Target offset
313     ; - Target segment
314     ; - Return offset
315     ; - Return segment (== real mode cs == 0)
316     ; - Return flags
317     ;
318     com32_farcall:
319     pushfd ; Save IF among other things...
320     pushad ; We only need to save some, but...
321    
322     mov eax,[esp+10*4] ; CS:IP
323     jmp com32_syscall
324    
325    
326     com32_intcall:
327     pushfd ; Save IF among other things...
328     pushad ; We only need to save some, but...
329    
330     movzx eax,byte [esp+10*4] ; INT number
331     mov eax,[eax*4] ; Get CS:IP from low memory
332    
333     com32_syscall:
334     cld
335    
336 niro 1133 movzx edi,word [word RealModeSSSP]
337     movzx ebx,word [word RealModeSSSP+2]
338 niro 532 sub edi,54 ; Allocate 54 bytes
339 niro 1133 mov [word RealModeSSSP],di
340 niro 532 shl ebx,4
341     add edi,ebx ; Create linear address
342    
343     mov esi,[esp+11*4] ; Source regs
344     xor ecx,ecx
345     mov cl,11 ; 44 bytes to copy
346     rep movsd
347    
348     ; EAX is already set up to be CS:IP
349     stosd ; Save in stack frame
350     mov eax,com32_sys_rm.return ; Return seg:offs
351     stosd ; Save in stack frame
352     mov eax,[edi-12] ; Return flags
353     and eax,0x200cd7 ; Mask (potentially) unsafe flags
354     mov [edi-12],eax ; Primary flags entry
355     stosw ; Return flags
356    
357     mov bx,com32_sys_rm
358     jmp com32_enter_rm ; Go to real mode
359    
360     ; On return, the 44-byte return structure is on the
361     ; real-mode stack, plus the 10 additional bytes used
362     ; by the target address (see above.)
363 niro 1133 .resume:
364     movzx esi,word [word RealModeSSSP]
365     movzx eax,word [word RealModeSSSP+2]
366 niro 532 mov edi,[esp+12*4] ; Dest regs
367     shl eax,4
368     add esi,eax ; Create linear address
369     and edi,edi ; NULL pointer?
370     jnz .do_copy
371     .no_copy: mov edi,esi ; Do a dummy copy-to-self
372     .do_copy: xor ecx,ecx
373     mov cl,11 ; 44 bytes
374     rep movsd ; Copy register block
375    
376 niro 1133 add dword [word RealModeSSSP],54 ; Remove from stack
377 niro 532
378     popad
379     popfd
380     ret ; Return to 32-bit program
381    
382 niro 1133 ;
383     ; Cfarcall invocation. We copy the stack frame to the real-mode stack,
384     ; followed by the return CS:IP and the CS:IP of the target function.
385     ;
386     com32_cfarcall:
387     pushfd
388     pushad
389    
390     cld
391     mov ecx,[esp+12*4] ; Size of stack frame
392    
393     movzx edi,word [word RealModeSSSP]
394     movzx ebx,word [word RealModeSSSP+2]
395     mov [word Com32SysSP],di
396     sub edi,ecx ; Allocate space for stack frame
397     and edi,~3 ; Round
398     sub edi,4*2 ; Return pointer, return value
399     mov [word RealModeSSSP],di
400     shl ebx,4
401     add edi,ebx ; Create linear address
402    
403     mov eax,[esp+10*4] ; CS:IP
404     stosd ; Save to stack frame
405     mov eax,com32_cfar_rm.return ; Return seg:off
406     stosd
407     mov esi,[esp+11*4] ; Stack frame
408     mov eax,ecx ; Copy the stack frame
409     shr ecx,2
410     rep movsd
411     mov ecx,eax
412     and ecx,3
413     rep movsb
414    
415     mov bx,com32_cfar_rm
416     jmp com32_enter_rm
417    
418     .resume:
419     popad
420     mov eax,[word RealModeEAX]
421     popfd
422     ret
423    
424 niro 532 bits 16
425    
426 niro 1133 section .bss1
427 niro 532 alignb 4
428 niro 1133 RealModeSSSP resd 1 ; Real-mode SS:SP
429     RealModeEAX resd 1 ; Real mode EAX
430 niro 532 PMESP resd 1 ; Protected-mode ESP
431     Com32SysSP resw 1 ; SP saved during COM32 syscall
432    
433 niro 1133 section .uibss
434     %if IS_SYSLINUX
435     Com32Name resb FILENAME_MAX+2
436     %else
437     Com32Name resb FILENAME_MAX
438     %endif
439    
440 niro 532 section .text