Add qemu 2.4.0
[kvmfornfv.git] / qemu / roms / ipxe / src / arch / i386 / prefix / dskprefix.S
1 /* NOTE: this boot sector contains instructions that need at least an 80186.
2  * Yes, as86 has a bug somewhere in the valid instruction set checks.
3  *
4  */
5
6 /*      floppyload.S Copyright (C) 1991, 1992 Linus Torvalds
7  *      modified by Drew Eckhardt
8  *      modified by Bruce Evans (bde)
9  *
10  * floppyprefix.S is loaded at 0x0000:0x7c00 by the bios-startup routines.
11  *
12  * It then loads the system at SYSSEG<<4, using BIOS interrupts.
13  *
14  * The loader has been made as simple as possible, and continuous read errors
15  * will result in a unbreakable loop. Reboot by hand. It loads pretty fast by
16  * getting whole tracks at a time whenever possible.
17  */
18
19 FILE_LICENCE ( GPL2_ONLY )
20
21 .equ    BOOTSEG, 0x07C0                 /* original address of boot-sector */
22
23 .equ    SYSSEG, 0x1000                  /* system loaded at SYSSEG<<4 */
24
25         .org    0
26         .arch i386
27         .text
28         .section ".prefix", "ax", @progbits
29         .code16
30         .globl  _dsk_start
31 _dsk_start:
32
33         jmp     $BOOTSEG, $go           /* reload cs:ip to match relocation addr */
34 go: 
35         movw    $0x2000-12, %di         /* 0x2000 is arbitrary value >= length */
36                                         /* of bootsect + room for stack + 12 for */
37                                         /* saved disk parm block */
38
39         movw    $BOOTSEG, %ax
40         movw    %ax,%ds
41         movw    %ax,%es
42         movw    %ax,%ss                 /* put stack at BOOTSEG:0x4000-12. */
43         movw    %di,%sp
44
45 /* Many BIOS's default disk parameter tables will not recognize multi-sector
46  * reads beyond the maximum sector number specified in the default diskette
47  * parameter tables - this may mean 7 sectors in some cases.
48  *
49  * Since single sector reads are slow and out of the question, we must take care
50  * of this by creating new parameter tables (for the first disk) in RAM.  We
51  * will set the maximum sector count to 36 - the most we will encounter on an
52  * ED 2.88.  High doesn't hurt. Low does.
53  *
54  * Segments are as follows: ds=es=ss=cs - BOOTSEG
55  */
56
57         xorw    %cx,%cx
58         movw    %cx,%es                 /* access segment 0 */
59         movw    $0x78, %bx              /* 0:bx is parameter table address */
60         pushw   %ds                     /* save ds */
61 /* 0:bx is parameter table address */
62         ldsw    %es:(%bx),%si           /* loads ds and si */
63
64         movw    %ax,%es                 /* ax is BOOTSECT (loaded above) */
65         movb    $6, %cl                 /* copy 12 bytes */
66         cld
67         pushw   %di                     /* keep a copy for later */
68         rep
69         movsw                           /* ds:si is source, es:di is dest */
70         popw    %di
71
72         movb    $36,%es:4(%di)
73
74         movw    %cx,%ds                 /* access segment 0 */
75         xchgw   %di,(%bx)
76         movw    %es,%si
77         xchgw   %si,2(%bx)
78         popw    %ds                     /* restore ds */
79         movw    %di, dpoff              /* save old parameters */
80         movw    %si, dpseg              /* to restore just before finishing */
81         pushw   %ds
82         popw    %es                     /* reload es */
83
84 /* Note that es is already set up.  Also cx is 0 from rep movsw above. */
85
86         xorb    %ah,%ah                 /* reset FDC */
87         xorb    %dl,%dl
88         int     $0x13
89
90 /* Get disk drive parameters, specifically number of sectors/track.
91  *
92  * It seems that there is no BIOS call to get the number of sectors.  Guess
93  * 36 sectors if sector 36 can be read, 18 sectors if sector 18 can be read,
94  * 15 if sector 15 can be read. Otherwise guess 9.
95  */
96
97         movw    $disksizes, %si         /* table of sizes to try */
98
99 probe_loop: 
100         lodsb
101         cbtw                            /* extend to word */
102         movw    %ax, sectors
103         cmpw    $disksizes+4, %si
104         jae     got_sectors             /* if all else fails, try 9 */
105         xchgw   %cx,%ax                 /* cx = track and sector */
106         xorw    %dx,%dx                 /* drive 0, head 0 */
107         movw    $0x0200, %bx            /* address after boot sector */
108                                         /*   (512 bytes from origin, es = cs) */
109         movw    $0x0201, %ax            /* service 2, 1 sector */
110         int     $0x13
111         jc      probe_loop              /* try next value */
112
113 got_sectors: 
114         movw    $msg1end-msg1, %cx
115         movw    $msg1, %si
116         call    print_str
117
118 /* ok, we've written the Loading... message, now we want to load the system */
119
120         movw    $SYSSEG, %ax
121         movw    %ax,%es                 /* segment of SYSSEG<<4 */
122         pushw   %es
123         call    read_it
124
125 /* This turns off the floppy drive motor, so that we enter the kernel in a
126  * known state, and don't have to worry about it later.
127  */
128         movw    $0x3f2, %dx
129         xorb    %al,%al
130         outb    %al,%dx
131
132         call    print_nl
133         pop     %es                     /* = SYSSEG */
134
135 /* Restore original disk parameters */
136         movw    $0x78, %bx
137         movw    dpoff, %di
138         movw    dpseg, %si
139         xorw    %ax,%ax
140         movw    %ax,%ds
141         movw    %di,(%bx)
142         movw    %si,2(%bx)
143
144         /* Everything now loaded.  %es = SYSSEG, so %es:0000 points to
145          * start of loaded image.
146          */
147
148         /* Jump to loaded copy */
149         ljmp    $SYSSEG, $start_runtime
150
151 endseg: .word SYSSEG
152         .section ".zinfo.fixup", "a", @progbits /* Compressor fixups */
153         .ascii  "ADDW"
154         .long   endseg
155         .long   16
156         .long   0
157         .previous
158
159 /* This routine loads the system at address SYSSEG<<4, making sure no 64kB
160  * boundaries are crossed. We try to load it as fast as possible, loading whole
161  * tracks whenever we can.
162  *
163  * in:  es - starting address segment (normally SYSSEG)
164  */
165 read_it: 
166         movw    $0,sread                /* load whole image including prefix */
167         movw    %es,%ax
168         testw   $0x0fff, %ax
169 die:    jne     die                     /* es must be at 64kB boundary */
170         xorw    %bx,%bx                 /* bx is starting address within segment */
171 rp_read: 
172         movw    %es,%ax
173         movw    %bx,%dx
174         movb    $4, %cl
175         shrw    %cl,%dx                 /* bx is always divisible by 16 */
176         addw    %dx,%ax
177         cmpw    endseg, %ax     /* have we loaded all yet? */
178         jb      ok1_read
179         ret
180 ok1_read: 
181         movw    sectors, %ax
182         subw    sread, %ax
183         movw    %ax,%cx
184         shlw    $9, %cx
185         addw    %bx,%cx
186         jnc     ok2_read
187         je      ok2_read
188         xorw    %ax,%ax
189         subw    %bx,%ax
190         shrw    $9, %ax
191 ok2_read: 
192         call    read_track
193         movw    %ax,%cx
194         addw    sread, %ax
195         cmpw    sectors, %ax
196         jne     ok3_read
197         movw    $1, %ax
198         subw    head, %ax
199         jne     ok4_read
200         incw    track
201 ok4_read: 
202         movw    %ax, head
203         xorw    %ax,%ax
204 ok3_read: 
205         movw    %ax, sread
206         shlw    $9, %cx
207         addw    %cx,%bx
208         jnc     rp_read
209         movw    %es,%ax
210         addb    $0x10, %ah
211         movw    %ax,%es
212         xorw    %bx,%bx
213         jmp     rp_read
214
215 read_track: 
216         pusha
217         pushw   %ax
218         pushw   %bx
219         pushw   %bp                     /* just in case the BIOS is buggy */
220         movw    $0x0e2e, %ax            /* 0x2e = . */
221         movw    $0x0007, %bx
222         int     $0x10
223         popw    %bp
224         popw    %bx
225         popw    %ax
226
227         movw    track, %dx
228         movw    sread, %cx
229         incw    %cx
230         movb    %dl,%ch
231         movw    head, %dx
232         movb    %dl,%dh
233         andw    $0x0100, %dx
234         movb    $2, %ah
235
236         pushw   %dx                     /* save for error dump */
237         pushw   %cx
238         pushw   %bx
239         pushw   %ax
240
241         int     $0x13
242         jc      bad_rt
243         addw    $8, %sp
244         popa
245         ret
246
247 bad_rt: pushw   %ax                     /* save error code */
248         call    print_all               /* ah = error, al = read */
249
250         xorb    %ah,%ah
251         xorb    %dl,%dl
252         int     $0x13
253
254         addw    $10, %sp
255         popa
256         jmp     read_track
257
258 /* print_all is for debugging purposes. It will print out all of the registers.
259  * The assumption is that this is called from a routine, with a stack frame like
260  *      dx
261  *      cx
262  *      bx
263  *      ax
264  *      error
265  *      ret <- sp
266  */
267
268 print_all: 
269         call    print_nl                /* nl for readability */
270         movw    $5, %cx                 /* error code + 4 registers */
271         movw    %sp,%bp
272
273 print_loop: 
274         pushw   %cx                     /* save count left */
275
276         cmpb    $5, %cl
277         jae     no_reg                  /* see if register name is needed */
278
279         movw    $0x0007, %bx            /* page 0, attribute 7 (normal) */
280         movw    $0xe05+0x41-1, %ax
281         subb    %cl,%al
282         int     $0x10
283
284         movb    $0x58, %al              /* 'X' */
285         int     $0x10
286
287         movb    $0x3A, %al              /* ':' */
288         int     $0x10
289
290 no_reg: 
291         addw    $2, %bp                 /* next register */
292         call    print_hex               /* print it */
293         movb    $0x20, %al              /* print a space */
294         int     $0x10
295         popw    %cx
296         loop    print_loop
297         call    print_nl                /* nl for readability */
298         ret
299
300 print_str: 
301         movw    $0x0007, %bx            /* page 0, attribute 7 (normal) */
302         movb    $0x0e, %ah              /* write char, tty mode */
303 prloop: 
304         lodsb
305         int     $0x10
306         loop    prloop
307         ret
308
309 print_nl: 
310         movw    $0x0007, %bx            /* page 0, attribute 7 (normal) */
311         movw    $0xe0d, %ax             /* CR */
312         int     $0x10
313         movb    $0xa, %al               /* LF */
314         int     $0x10
315         ret
316
317 /* print_hex prints the word pointed to by ss:bp in hexadecimal. */
318
319 print_hex: 
320         movw    (%bp),%dx               /* load word into dx */
321         movb    $4, %cl
322         movb    $0x0e, %ah              /* write char, tty mode */
323         movw    $0x0007, %bx            /* page 0, attribute 7 (normal) */
324         call    print_digit
325         call    print_digit
326         call    print_digit
327 /* fall through */
328 print_digit: 
329         rol     %cl,%dx                 /* rotate so that lowest 4 bits are used */
330         movb    $0x0f, %al              /* mask for nybble */
331         andb    %dl,%al
332         addb    $0x90, %al              /* convert al to ascii hex (four instructions) */
333         daa
334         adcb    $0x40, %al
335         daa
336         int     $0x10
337         ret
338
339 sread:  .word 0                         /* sectors read of current track */
340 head:   .word 0                         /* current head */
341 track:  .word 0                         /* current track */
342
343 sectors: 
344         .word 0
345
346 dpseg:  .word 0
347 dpoff:  .word 0
348
349 disksizes: 
350         .byte 36,18,15,9
351
352 msg1: 
353         .ascii "Loading ROM image"
354 msg1end: 
355
356         .org 510, 0
357         .word 0xAA55
358
359 start_runtime:
360         /* Install iPXE */
361         call    install
362
363         /* Set up real-mode stack */
364         movw    %bx, %ss
365         movw    $_estack16, %sp
366
367         /* Jump to .text16 segment */
368         pushw   %ax
369         pushw   $1f
370         lret
371         .section ".text16", "awx", @progbits
372 1:
373         pushl   $main
374         pushw   %cs
375         call    prot_call
376         popl    %ecx /* discard */
377
378         /* Uninstall iPXE */
379         call    uninstall
380
381         /* Boot next device */
382         int $0x18
383