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