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