ftp://ftp.kernel.org/pub/linux/kernel/v2.6/linux-2.6.6.tar.bz2
[linux-2.6.git] / arch / i386 / boot98 / setup.S
1 /*
2  *      setup.S         Copyright (C) 1991, 1992 Linus Torvalds
3  *
4  * setup.s is responsible for getting the system data from the BIOS,
5  * and putting them into the appropriate places in system memory.
6  * both setup.s and system has been loaded by the bootblock.
7  *
8  * This code asks the bios for memory/disk/other parameters, and
9  * puts them in a "safe" place: 0x90000-0x901FF, ie where the
10  * boot-block used to be. It is then up to the protected mode
11  * system to read them from there before the area is overwritten
12  * for buffer-blocks.
13  *
14  * Move PS/2 aux init code to psaux.c
15  * (troyer@saifr00.cfsat.Honeywell.COM) 03Oct92
16  *
17  * some changes and additional features by Christoph Niemann,
18  * March 1993/June 1994 (Christoph.Niemann@linux.org)
19  *
20  * add APM BIOS checking by Stephen Rothwell, May 1994
21  * (sfr@canb.auug.org.au)
22  *
23  * High load stuff, initrd support and position independency
24  * by Hans Lermen & Werner Almesberger, February 1996
25  * <lermen@elserv.ffm.fgan.de>, <almesber@lrc.epfl.ch>
26  *
27  * Video handling moved to video.S by Martin Mares, March 1996
28  * <mj@k332.feld.cvut.cz>
29  *
30  * Extended memory detection scheme retwiddled by orc@pell.chi.il.us (david
31  * parsons) to avoid loadlin confusion, July 1997
32  *
33  * Transcribed from Intel (as86) -> AT&T (gas) by Chris Noe, May 1999.
34  * <stiker@northlink.com>
35  *
36  * Fix to work around buggy BIOSes which dont use carry bit correctly
37  * and/or report extended memory in CX/DX for e801h memory size detection 
38  * call.  As a result the kernel got wrong figures.  The int15/e801h docs
39  * from Ralf Brown interrupt list seem to indicate AX/BX should be used
40  * anyway.  So to avoid breaking many machines (presumably there was a reason
41  * to orginally use CX/DX instead of AX/BX), we do a kludge to see
42  * if CX/DX have been changed in the e801 call and if so use AX/BX .
43  * Michael Miller, April 2001 <michaelm@mjmm.org>
44  *
45  * New A20 code ported from SYSLINUX by H. Peter Anvin. AMD Elan bugfixes
46  * by Robert Schwebel, December 2001 <robert@schwebel.de>
47  *
48  * Heavily modified for NEC PC-9800 series by Kyoto University Microcomputer
49  * Club (KMC) Linux/98 project <seraphim@kmc.kyoto-u.ac.jp>, 1997-1999
50  */
51
52 #include <linux/config.h>
53 #include <asm/segment.h>
54 #include <linux/version.h>
55 #include <linux/compile.h>
56 #include <asm/boot.h>
57 #include <asm/e820.h>
58 #include <asm/page.h>
59         
60 /* Signature words to ensure LILO loaded us right */
61 #define SIG1    0xAA55
62 #define SIG2    0x5A5A
63
64 #define HIRESO_TEXT     0xe000
65 #define NORMAL_TEXT     0xa000
66
67 #define BIOS_FLAG2      0x0400
68 #define BIOS_FLAG5      0x0458
69 #define RDISK_EQUIP     0x0488
70 #define BIOS_FLAG       0x0501
71 #define KB_SHFT_STS     0x053a
72 #define DISK_EQUIP      0x055c
73
74 INITSEG  = DEF_INITSEG          # 0x9000, we move boot here, out of the way
75 SYSSEG   = DEF_SYSSEG           # 0x1000, system loaded at 0x10000 (65536).
76 SETUPSEG = DEF_SETUPSEG         # 0x9020, this is the current segment
77                                 # ... and the former contents of CS
78
79 DELTA_INITSEG = SETUPSEG - INITSEG      # 0x0020
80
81 .code16
82 .globl begtext, begdata, begbss, endtext, enddata, endbss
83
84 .text
85 begtext:
86 .data
87 begdata:
88 .bss
89 begbss:
90 .text
91
92 start:
93         jmp     trampoline
94
95 # This is the setup header, and it must start at %cs:2 (old 0x9020:2)
96
97                 .ascii  "HdrS"          # header signature
98                 .word   0x0203          # header version number (>= 0x0105)
99                                         # or else old loadlin-1.5 will fail)
100 realmode_swtch: .word   0, 0            # default_switch, SETUPSEG
101 start_sys_seg:  .word   SYSSEG
102                 .word   kernel_version  # pointing to kernel version string
103                                         # above section of header is compatible
104                                         # with loadlin-1.5 (header v1.5). Don't
105                                         # change it.
106
107 type_of_loader: .byte   0               # = 0, old one (LILO, Loadlin,
108                                         #      Bootlin, SYSLX, bootsect...)
109                                         # See Documentation/i386/boot.txt for
110                                         # assigned ids
111         
112 # flags, unused bits must be zero (RFU) bit within loadflags
113 loadflags:
114 LOADED_HIGH     = 1                     # If set, the kernel is loaded high
115 CAN_USE_HEAP    = 0x80                  # If set, the loader also has set
116                                         # heap_end_ptr to tell how much
117                                         # space behind setup.S can be used for
118                                         # heap purposes.
119                                         # Only the loader knows what is free
120 #ifndef __BIG_KERNEL__
121                 .byte   0
122 #else
123                 .byte   LOADED_HIGH
124 #endif
125
126 setup_move_size: .word  0x8000          # size to move, when setup is not
127                                         # loaded at 0x90000. We will move setup 
128                                         # to 0x90000 then just before jumping
129                                         # into the kernel. However, only the
130                                         # loader knows how much data behind
131                                         # us also needs to be loaded.
132
133 code32_start:                           # here loaders can put a different
134                                         # start address for 32-bit code.
135 #ifndef __BIG_KERNEL__
136                 .long   0x1000          #   0x1000 = default for zImage
137 #else
138                 .long   0x100000        # 0x100000 = default for big kernel
139 #endif
140
141 ramdisk_image:  .long   0               # address of loaded ramdisk image
142                                         # Here the loader puts the 32-bit
143                                         # address where it loaded the image.
144                                         # This only will be read by the kernel.
145
146 ramdisk_size:   .long   0               # its size in bytes
147
148 bootsect_kludge:
149                 .word  bootsect_helper, SETUPSEG
150
151 heap_end_ptr:   .word   modelist+1024   # (Header version 0x0201 or later)
152                                         # space from here (exclusive) down to
153                                         # end of setup code can be used by setup
154                                         # for local heap purposes.
155
156 pad1:           .word   0
157 cmd_line_ptr:   .long 0                 # (Header version 0x0202 or later)
158                                         # If nonzero, a 32-bit pointer
159                                         # to the kernel command line.
160                                         # The command line should be
161                                         # located between the start of
162                                         # setup and the end of low
163                                         # memory (0xa0000), or it may
164                                         # get overwritten before it
165                                         # gets read.  If this field is
166                                         # used, there is no longer
167                                         # anything magical about the
168                                         # 0x90000 segment; the setup
169                                         # can be located anywhere in
170                                         # low memory 0x10000 or higher.
171
172 ramdisk_max:    .long MAXMEM-1          # (Header version 0x0203 or later)
173                                         # The highest safe address for
174                                         # the contents of an initrd
175
176 trampoline:     call    start_of_setup
177                 .space  1024
178 # End of setup header #####################################################
179
180 start_of_setup:
181 # Set %ds = %cs, we know that SETUPSEG = %cs at this point
182         movw    %cs, %ax                # aka SETUPSEG
183         movw    %ax, %ds
184 # Check signature at end of setup
185         cmpw    $SIG1, setup_sig1
186         jne     bad_sig
187
188         cmpw    $SIG2, setup_sig2
189         jne     bad_sig
190
191         jmp     good_sig1
192
193 # Routine to print asciiz string at ds:si
194 prtstr:
195         lodsb
196         andb    %al, %al
197         jz      fin
198
199         call    prtchr
200         jmp     prtstr
201
202 fin:    ret
203
204 no_sig_mess: .string    "No setup signature found ..."
205
206 good_sig1:
207         jmp     good_sig
208
209 # We now have to find the rest of the setup code/data
210 bad_sig:
211         movw    %cs, %ax                        # SETUPSEG
212         subw    $DELTA_INITSEG, %ax             # INITSEG
213         movw    %ax, %ds
214         xorb    %bh, %bh
215         movb    (497), %bl                      # get setup sect from bootsect
216         subw    $4, %bx                         # LILO loads 4 sectors of setup
217         shlw    $8, %bx                         # convert to words (1sect=2^8 words)
218         movw    %bx, %cx
219         shrw    $3, %bx                         # convert to segment
220         addw    $SYSSEG, %bx
221         movw    %bx, %cs:start_sys_seg
222 # Move rest of setup code/data to here
223         movw    $2048, %di                      # four sectors loaded by LILO
224         subw    %si, %si
225         pushw   %cs
226         popw    %es
227         movw    $SYSSEG, %ax
228         movw    %ax, %ds
229         rep
230         movsw
231         movw    %cs, %ax                        # aka SETUPSEG
232         movw    %ax, %ds
233         cmpw    $SIG1, setup_sig1
234         jne     no_sig
235
236         cmpw    $SIG2, setup_sig2
237         jne     no_sig
238
239         jmp     good_sig
240
241 no_sig:
242         lea     no_sig_mess, %si
243         call    prtstr
244
245 no_sig_loop:
246         hlt
247         jmp     no_sig_loop
248
249 good_sig:
250         movw    %cs, %ax                        # aka SETUPSEG
251         subw    $DELTA_INITSEG, %ax             # aka INITSEG
252         movw    %ax, %ds
253 # Check if an old loader tries to load a big-kernel
254         testb   $LOADED_HIGH, %cs:loadflags     # Do we have a big kernel?
255         jz      loader_ok                       # No, no danger for old loaders.
256
257         cmpb    $0, %cs:type_of_loader          # Do we have a loader that
258                                                 # can deal with us?
259         jnz     loader_ok                       # Yes, continue.
260
261         pushw   %cs                             # No, we have an old loader,
262         popw    %ds                             # die. 
263         lea     loader_panic_mess, %si
264         call    prtstr
265
266         jmp     no_sig_loop
267
268 loader_panic_mess: .string "Wrong loader, giving up..."
269
270 loader_ok:
271 # Get memory size (extended mem, kB)
272
273 # On PC-9800, memory size detection is done completely in 32-bit
274 # kernel initialize code (kernel/setup.c).
275         pushw   %es
276         xorl    %eax, %eax
277         movw    %ax, %es
278         movb    %al, (E820NR)           # PC-9800 has no E820
279         movb    %es:(0x401), %al
280         shll    $7, %eax
281         addw    $1024, %ax
282         movw    %ax, (2)
283         movl    %eax, (0x1e0)
284         movw    %es:(0x594), %ax
285         shll    $10, %eax
286         addl    %eax, (0x1e0)
287         popw    %es
288
289 # Check for video adapter and its parameters and allow the
290 # user to browse video modes.
291         call    video                           # NOTE: we need %ds pointing
292                                                 # to bootsector
293
294 # Get text video mode
295         movb    $0x0B, %ah
296         int     $0x18           # CRT mode sense
297         movw    $(20 << 8) + 40, %cx
298         testb   $0x10, %al
299         jnz     3f
300         movb    $20, %ch
301         testb   $0x01, %al
302         jnz     1f
303         movb    $25, %ch
304         jmp     1f
305 3:      # If bit 4 was 1, it means either 1) 31 lines for hi-reso mode,
306         # or 2) 30 lines for PC-9821.
307         movb    $31, %ch        # hireso mode value
308         pushw   $0
309         popw    %es
310         testb   $0x08, %es:BIOS_FLAG
311         jnz     1f
312         movb    $30, %ch
313 1:      # Now we got # of rows in %ch
314         movb    %ch, (14)
315
316         testb   $0x02, %al
317         jnz     2f
318         movb    $80, %cl
319 2:      # Now we got # of columns in %cl
320         movb    %cl, (7)
321
322         # Next, get horizontal frequency if supported
323         movw    $0x3100, %ax
324         int     $0x18           # Call CRT bios
325         movb    %al, (6)        # If 31h is unsupported, %al remains 0
326
327 # Get hd0-3 data...
328         pushw   %ds                             # aka INITSEG
329         popw    %es
330         xorw    %ax, %ax
331         movw    %ax, %ds
332         cld
333         movw    $0x0080, %di
334         movb    DISK_EQUIP+1, %ah
335         movb    $0x80, %al
336
337 get_hd_info:
338         shrb    %ah
339         pushw   %ax
340         jnc     1f
341         movb    $0x84, %ah
342         int     $0x1b
343         jnc     2f                              # Success
344 1:      xorw    %cx, %cx                        # `0 cylinders' means no drive
345 2:      # Attention! Work area (drive_info) is arranged for PC-9800.
346         movw    %cx, %ax                        # # of cylinders
347         stosw
348         movw    %dx, %ax                        # # of sectors / # of heads
349         stosw
350         movw    %bx, %ax                        # sector size in bytes
351         stosw
352         popw    %ax
353         incb    %al
354         cmpb    $0x84, %al
355         jb      get_hd_info
356
357 # Get fd data...
358         movw    DISK_EQUIP, %ax
359         andw    $0xf00f, %ax
360         orb     %al, %ah
361         movb    RDISK_EQUIP, %al
362         notb    %al
363         andb    %al, %ah                        # ignore all `RAM drive'
364
365         movb    $0x30, %al
366
367 get_fd_info:
368         shrb    %ah
369         pushw   %ax
370         jnc     1f
371         movb    $0xc4, %ah
372         int     $0x1b
373         movb    %ah, %al
374         andb    $4, %al                         # 1.44MB support flag
375         shrb    %al
376         addb    $2, %al                         # %al = 2 (1.2MB) or 4 (1.44MB)
377         jmp     2f
378 1:      movb    $0, %al                         # no drive
379 2:      stosb
380         popw    %ax
381         incb    %al
382         testb   $0x04, %al
383         jz      get_fd_info
384
385         addb    $(0xb0 - 0x34), %al
386         jnc     get_fd_info                     # check FDs on 640KB I/F
387
388         pushw   %es
389         popw    %ds                             # %ds got bootsector again
390 #if 0
391         mov     $0, (0x1ff)                     # default is no pointing device
392 #endif
393
394 #if defined(CONFIG_APM) || defined(CONFIG_APM_MODULE)
395 # Then check for an APM BIOS...
396                                                 # %ds points to the bootsector
397         movw    $0, 0x40                        # version = 0 means no APM BIOS
398         movw    $0x09a00, %ax                   # APM BIOS installation check
399         xorw    %bx, %bx
400         int     $0x1f
401         jc      done_apm_bios                   # Nope, no APM BIOS
402
403         cmpw    $0x0504d, %bx                   # Check for "PM" signature
404         jne     done_apm_bios                   # No signature, no APM BIOS
405
406         testb   $0x02, %cl                      # Is 32 bit supported?
407         je      done_apm_bios                   # No 32-bit, no (good) APM BIOS
408
409         movw    $0x09a04, %ax                   # Disconnect first just in case
410         xorw    %bx, %bx
411         int     $0x1f                           # ignore return code
412         movw    $0x09a03, %ax                   # 32 bit connect
413         xorl    %ebx, %ebx
414         int     $0x1f
415         jc      no_32_apm_bios                  # Ack, error.
416
417         movw    %ax,  (66)                      # BIOS code segment
418         movl    %ebx, (68)                      # BIOS entry point offset
419         movw    %cx,  (72)                      # BIOS 16 bit code segment
420         movw    %dx,  (74)                      # BIOS data segment
421         movl    %esi, (78)                      # BIOS code segment length
422         movw    %di,  (82)                      # BIOS data segment length
423 # Redo the installation check as the 32 bit connect
424 # modifies the flags returned on some BIOSs
425         movw    $0x09a00, %ax                   # APM BIOS installation check
426         xorw    %bx, %bx
427         int     $0x1f
428         jc      apm_disconnect                  # error -> shouldn't happen
429
430         cmpw    $0x0504d, %bx                   # check for "PM" signature
431         jne     apm_disconnect                  # no sig -> shouldn't happen
432
433         movw    %ax, (64)                       # record the APM BIOS version
434         movw    %cx, (76)                       # and flags
435         jmp     done_apm_bios
436
437 apm_disconnect:                                 # Tidy up
438         movw    $0x09a04, %ax                   # Disconnect
439         xorw    %bx, %bx
440         int     $0x1f                           # ignore return code
441
442         jmp     done_apm_bios
443
444 no_32_apm_bios:
445         andw    $0xfffd, (76)                   # remove 32 bit support bit
446 done_apm_bios:
447 #endif
448
449 # Pass cursor position to kernel...
450         movw    %cs:cursor_address, %ax
451         shrw    %ax             # cursor_address is 2 bytes unit
452         movb    $80, %cl
453         divb    %cl
454         xchgb   %al, %ah        # (0) = %al = X, (1) = %ah = Y
455         movw    %ax, (0)
456
457 #if 0
458         movw    $msg_cpos, %si
459         call    prtstr_cs
460         call    prthex
461         call    prtstr_cs
462         movw    %ds, %ax
463         call    prthex
464         call    prtstr_cs
465         movb    $0x11, %ah
466         int     $0x18
467         movb    $0, %ah
468         int     $0x18
469         .section .rodata, "a"
470 msg_cpos:       .string "Cursor position: 0x"
471                 .string ", %ds:0x"
472                 .string "\r\n"
473         .previous
474 #endif
475
476 # Now we want to move to protected mode ...
477         cmpw    $0, %cs:realmode_swtch
478         jz      rmodeswtch_normal
479
480         lcall   *%cs:realmode_swtch
481
482         jmp     rmodeswtch_end
483
484 rmodeswtch_normal:
485         pushw   %cs
486         call    default_switch
487
488 rmodeswtch_end:
489 # we get the code32 start address and modify the below 'jmpi'
490 # (loader may have changed it)
491         movl    %cs:code32_start, %eax
492         movl    %eax, %cs:code32
493
494 # Now we move the system to its rightful place ... but we check if we have a
495 # big-kernel. In that case we *must* not move it ...
496         testb   $LOADED_HIGH, %cs:loadflags
497         jz      do_move0                        # .. then we have a normal low
498                                                 # loaded zImage
499                                                 # .. or else we have a high
500                                                 # loaded bzImage
501         jmp     end_move                        # ... and we skip moving
502
503 do_move0:
504         movw    $0x100, %ax                     # start of destination segment
505         movw    %cs, %bp                        # aka SETUPSEG
506         subw    $DELTA_INITSEG, %bp             # aka INITSEG
507         movw    %cs:start_sys_seg, %bx          # start of source segment
508         cld
509 do_move:
510         movw    %ax, %es                        # destination segment
511         incb    %ah                             # instead of add ax,#0x100
512         movw    %bx, %ds                        # source segment
513         addw    $0x100, %bx
514         subw    %di, %di
515         subw    %si, %si
516         movw    $0x800, %cx
517         rep
518         movsw
519         cmpw    %bp, %bx                        # assume start_sys_seg > 0x200,
520                                                 # so we will perhaps read one
521                                                 # page more than needed, but
522                                                 # never overwrite INITSEG
523                                                 # because destination is a
524                                                 # minimum one page below source
525         jb      do_move
526
527 end_move:
528 # then we load the segment descriptors
529         movw    %cs, %ax                        # aka SETUPSEG
530         movw    %ax, %ds
531                
532 # Check whether we need to be downward compatible with version <=201
533         cmpl    $0, cmd_line_ptr
534         jne     end_move_self           # loader uses version >=202 features
535         cmpb    $0x20, type_of_loader
536         je      end_move_self           # bootsect loader, we know of it
537  
538 # Boot loader does not support boot protocol version 2.02.
539 # If we have our code not at 0x90000, we need to move it there now.
540 # We also then need to move the params behind it (commandline)
541 # Because we would overwrite the code on the current IP, we move
542 # it in two steps, jumping high after the first one.
543         movw    %cs, %ax
544         cmpw    $SETUPSEG, %ax
545         je      end_move_self
546
547         cli                                     # make sure we really have
548                                                 # interrupts disabled !
549                                                 # because after this the stack
550                                                 # should not be used
551         subw    $DELTA_INITSEG, %ax             # aka INITSEG
552         movw    %ss, %dx
553         cmpw    %ax, %dx
554         jb      move_self_1
555
556         addw    $INITSEG, %dx
557         subw    %ax, %dx                        # this will go into %ss after
558                                                 # the move
559 move_self_1:
560         movw    %ax, %ds
561         movw    $INITSEG, %ax                   # real INITSEG
562         movw    %ax, %es
563         movw    %cs:setup_move_size, %cx
564         std                                     # we have to move up, so we use
565                                                 # direction down because the
566                                                 # areas may overlap
567         movw    %cx, %di
568         decw    %di
569         movw    %di, %si
570         subw    $move_self_here+0x200, %cx
571         rep
572         movsb
573         ljmp    $SETUPSEG, $move_self_here
574
575 move_self_here:
576         movw    $move_self_here+0x200, %cx
577         rep
578         movsb
579         movw    $SETUPSEG, %ax
580         movw    %ax, %ds
581         movw    %dx, %ss
582
583 end_move_self:                                  # now we are at the right place
584         lidt    idt_48                          # load idt with 0,0
585         xorl    %eax, %eax                      # Compute gdt_base
586         movw    %ds, %ax                        # (Convert %ds:gdt to a linear ptr)
587         shll    $4, %eax
588         addl    $gdt, %eax
589         movl    %eax, (gdt_48+2)
590         lgdt    gdt_48                          # load gdt with whatever is
591                                                 # appropriate
592
593 # that was painless, now we enable A20
594
595         outb    %al, $0xf2                      # A20 on
596         movb    $0x02, %al
597         outb    %al, $0xf6                      # also A20 on; making ITF's
598                                                 # way our model
599
600         # PC-9800 seems to enable A20 at the moment of `outb';
601         # so we don't wait unlike IBM PCs (see ../setup.S).
602
603 # enable DMA to access memory over 0x100000 (1MB).
604
605         movw    $0x439, %dx
606         inb     %dx, %al
607         andb    $(~4), %al
608         outb    %al, %dx
609
610 # Set DMA to increment its bank address automatically at 16MB boundary.
611 # Initial setting is 64KB boundary mode so that we can't run DMA crossing
612 # physical address 0xXXXXFFFF.
613
614         movb    $0x0c, %al
615         outb    %al, $0x29                      # ch. 0
616         movb    $0x0d, %al
617         outb    %al, $0x29                      # ch. 1
618         movb    $0x0e, %al
619         outb    %al, $0x29                      # ch. 2
620         movb    $0x0f, %al
621         outb    %al, $0x29                      # ch. 3
622         movb    $0x50, %al
623         outb    %al, $0x11                      # reinitialize DMAC
624
625 # make sure any possible coprocessor is properly reset..
626         movb    $0, %al
627         outb    %al, $0xf8
628         outb    %al, $0x5f                      # delay
629
630 # well, that went ok, I hope. Now we mask all interrupts - the rest
631 # is done in init_IRQ().
632         movb    $0xFF, %al                      # mask all interrupts for now
633         outb    %al, $0x0A
634         outb    %al, $0x5f                      # delay
635         
636         movb    $0x7F, %al                      # mask all irq's but irq7 which
637         outb    %al, $0x02                      # is cascaded
638
639 # Well, that certainly wasn't fun :-(. Hopefully it works, and we don't
640 # need no steenking BIOS anyway (except for the initial loading :-).
641 # The BIOS-routine wants lots of unnecessary data, and it's less
642 # "interesting" anyway. This is how REAL programmers do it.
643 #
644 # Well, now's the time to actually move into protected mode. To make
645 # things as simple as possible, we do no register set-up or anything,
646 # we let the gnu-compiled 32-bit programs do that. We just jump to
647 # absolute address 0x1000 (or the loader supplied one),
648 # in 32-bit protected mode.
649 #
650 # Note that the short jump isn't strictly needed, although there are
651 # reasons why it might be a good idea. It won't hurt in any case.
652         movw    $1, %ax                         # protected mode (PE) bit
653         lmsw    %ax                             # This is it!
654         jmp     flush_instr
655
656 flush_instr:
657         xorw    %bx, %bx                        # Flag to indicate a boot
658         xorl    %esi, %esi                      # Pointer to real-mode code
659         movw    %cs, %si
660         subw    $DELTA_INITSEG, %si
661         shll    $4, %esi                        # Convert to 32-bit pointer
662 # NOTE: For high loaded big kernels we need a
663 #       jmpi    0x100000,__BOOT_CS
664 #
665 #       but we yet haven't reloaded the CS register, so the default size 
666 #       of the target offset still is 16 bit.
667 #       However, using an operand prefix (0x66), the CPU will properly
668 #       take our 48 bit far pointer. (INTeL 80386 Programmer's Reference
669 #       Manual, Mixing 16-bit and 32-bit code, page 16-6)
670
671         .byte 0x66, 0xea                        # prefix + jmpi-opcode
672 code32: .long   0x1000                          # will be set to 0x100000
673                                                 # for big kernels
674         .word   __BOOT_CS
675
676 # Here's a bunch of information about your current kernel..
677 kernel_version: .ascii  UTS_RELEASE
678                 .ascii  " ("
679                 .ascii  LINUX_COMPILE_BY
680                 .ascii  "@"
681                 .ascii  LINUX_COMPILE_HOST
682                 .ascii  ") "
683                 .ascii  UTS_VERSION
684                 .byte   0
685
686 # This is the default real mode switch routine.
687 # to be called just before protected mode transition
688 default_switch:
689         cli                                     # no interrupts allowed !
690         outb    %al, $0x50                      # disable NMI for bootup
691                                                 # sequence
692         lret
693
694 # This routine only gets called, if we get loaded by the simple
695 # bootsect loader _and_ have a bzImage to load.
696 # Because there is no place left in the 512 bytes of the boot sector,
697 # we must emigrate to code space here.
698 bootsect_helper:
699         cmpw    $0, %cs:bootsect_es
700         jnz     bootsect_second
701
702         movb    $0x20, %cs:type_of_loader
703         movw    %es, %ax
704         shrw    $4, %ax
705         movb    %ah, %cs:bootsect_src_base+2
706         movw    %es, %ax
707         movw    %ax, %cs:bootsect_es
708         subw    $SYSSEG, %ax
709         lret                                    # nothing else to do for now
710
711 bootsect_second:
712         pushw   %bx
713         pushw   %cx
714         pushw   %si
715         pushw   %di
716         testw   %bp, %bp                        # 64K full ?
717         jne     bootsect_ex
718
719         xorw    %cx, %cx                        # zero means full 64K
720         pushw   %cs
721         popw    %es
722         movw    $bootsect_gdt, %bx
723         xorw    %si, %si                        # source address
724         xorw    %di, %di                        # destination address
725         movb    $0x90, %ah
726         int     $0x1f
727         jc      bootsect_panic                  # this, if INT1F fails
728
729         movw    %cs:bootsect_es, %es            # we reset %es to always point
730         incb    %cs:bootsect_dst_base+2         # to 0x10000
731 bootsect_ex:
732         movb    %cs:bootsect_dst_base+2, %ah
733         shlb    $4, %ah                         # we now have the number of
734                                                 # moved frames in %ax
735         xorb    %al, %al
736         popw    %di
737         popw    %si
738         popw    %cx
739         popw    %bx
740         lret
741
742 bootsect_gdt:
743         .word   0, 0, 0, 0
744         .word   0, 0, 0, 0
745
746 bootsect_src:
747         .word   0xffff
748
749 bootsect_src_base:
750         .byte   0x00, 0x00, 0x01                # base = 0x010000
751         .byte   0x93                            # typbyte
752         .word   0                               # limit16,base24 =0
753
754 bootsect_dst:
755         .word   0xffff
756
757 bootsect_dst_base:
758         .byte   0x00, 0x00, 0x10                # base = 0x100000
759         .byte   0x93                            # typbyte
760         .word   0                               # limit16,base24 =0
761         .word   0, 0, 0, 0                      # BIOS CS
762         .word   0, 0, 0, 0                      # BIOS DS
763
764 bootsect_es:
765         .word   0
766
767 bootsect_panic:
768         pushw   %cs
769         popw    %ds
770         cld
771         leaw    bootsect_panic_mess, %si
772         call    prtstr
773
774 bootsect_panic_loop:
775         jmp     bootsect_panic_loop
776
777 bootsect_panic_mess:
778         .string "INT1F refuses to access high mem, giving up."
779
780 # This routine prints one character (in %al) on console.
781 # PC-9800 doesn't have BIOS-function to do it like IBM PC's INT 10h - 0Eh,
782 # so we hardcode `prtchr' subroutine here.
783 prtchr:
784         pushaw
785         pushw   %es
786         cmpb    $0, %cs:prtchr_initialized
787         jnz     prtchr_ok
788         xorw    %cx, %cx
789         movw    %cx, %es
790         testb   $0x8, %es:BIOS_FLAG
791         jz      1f
792         movb    $(HIRESO_TEXT >> 8), %cs:cursor_address+3
793         movw    $(80 * 31 * 2), %cs:max_cursor_offset
794 1:      pushw   %ax
795         call    get_cursor_position
796         movw    %ax, %cs:cursor_address
797         popw    %ax
798         movb    $1, %cs:prtchr_initialized
799 prtchr_ok:
800         lesw    %cs:cursor_address, %di
801         movw    $160, %bx
802         movb    $0, %ah
803         cmpb    $13, %al
804         je      do_cr
805         cmpb    $10, %al
806         je      do_lf
807
808         # normal (printable) character
809         stosw
810         movb    $0xe1, %es:0x2000-2(%di)
811         jmp     1f
812
813 do_cr:  movw    %di, %ax
814         divb    %bl                             # %al = Y, %ah = X * 2
815         mulb    %bl
816         movw    %ax, %dx
817         jmp     2f
818
819 do_lf:  addw    %bx, %di
820 1:      movw    %cs:max_cursor_offset, %cx
821         cmpw    %cx, %di
822         movw    %di, %dx
823         jb      2f
824         # cursor reaches bottom of screen; scroll it
825         subw    %bx, %dx
826         xorw    %di, %di
827         movw    %bx, %si
828         cld
829         subw    %bx, %cx
830         shrw    %cx
831         pushw   %cx
832         rep; es; movsw
833         movb    $32, %al                        # clear bottom line characters
834         movb    $80, %cl
835         rep; stosw
836         movw    $0x2000, %di
837         popw    %cx
838         leaw    (%bx,%di), %si
839         rep; es; movsw
840         movb    $0xe1, %al                      # clear bottom line attributes
841         movb    $80, %cl
842         rep; stosw
843 2:      movw    %dx, %cs:cursor_address
844         movb    $0x13, %ah                      # move cursor to right position
845         int     $0x18
846         popw    %es
847         popaw
848         ret
849
850 cursor_address:
851         .word   0
852         .word   NORMAL_TEXT
853 max_cursor_offset:
854         .word   80 * 25 * 2                     # for normal 80x25 mode
855
856 # putstr may called without running through start_of_setup (via bootsect_panic)
857 # so we should initialize ourselves on demand.
858 prtchr_initialized:
859         .byte   0
860
861 # This routine queries GDC (graphic display controller) for current cursor
862 # position. Cursor position is returned in %ax (CPU offset address).
863 get_cursor_position:
864 1:      inb     $0x60, %al
865         outb    %al, $0x5f                      # delay
866         outb    %al, $0x5f                      # delay
867         testb   $0x04, %al                      # Is FIFO empty?
868         jz      1b                              # no -> wait until empty
869
870         movb    $0xe0, %al                      # CSRR command
871         outb    %al, $0x62                      # command write
872         outb    %al, $0x5f                      # delay
873         outb    %al, $0x5f                      # delay
874
875 2:      inb     $0x60, %al
876         outb    %al, $0x5f                      # delay
877         outb    %al, $0x5f                      # delay
878         testb   $0x01, %al                      # Is DATA READY?
879         jz      2b                              # no -> wait until ready
880
881         inb     $0x62, %al                      # read xAD (L)
882         outb    %al, $0x5f                      # delay
883         outb    %al, $0x5f                      # delay
884         movb    %al, %ah
885         inb     $0x62, %al                      # read xAD (H)
886         outb    %al, $0x5f                      # delay
887         outb    %al, $0x5f                      # delay
888         xchgb   %al, %ah                        # correct byte order
889         pushw   %ax
890         inb     $0x62, %al                      # read yAD (L)
891         outb    %al, $0x5f                      # delay
892         outb    %al, $0x5f                      # delay
893         inb     $0x62, %al                      # read yAD (M)
894         outb    %al, $0x5f                      # delay
895         outb    %al, $0x5f                      # delay
896         inb     $0x62, %al                      # read yAD (H)
897                                                 # yAD is not our interest,
898                                                 # so discard it.
899         popw    %ax
900         addw    %ax, %ax                        # convert to CPU address
901         ret
902
903 # Descriptor tables
904 #
905 # NOTE: The intel manual says gdt should be sixteen bytes aligned for
906 # efficiency reasons.  However, there are machines which are known not
907 # to boot with misaligned GDTs, so alter this at your peril!  If you alter
908 # GDT_ENTRY_BOOT_CS (in asm/segment.h) remember to leave at least two
909 # empty GDT entries (one for NULL and one reserved).
910 #
911 # NOTE: On some CPUs, the GDT must be 8 byte aligned.  This is
912 # true for the Voyager Quad CPU card which will not boot without
913 # This directive.  16 byte aligment is recommended by intel.
914 #
915         .align 16
916 gdt:
917         .fill GDT_ENTRY_BOOT_CS,8,0
918
919         .word   0xFFFF                          # 4Gb - (0x100000*0x1000 = 4Gb)
920         .word   0                               # base address = 0
921         .word   0x9A00                          # code read/exec
922         .word   0x00CF                          # granularity = 4096, 386
923                                                 #  (+5th nibble of limit)
924
925         .word   0xFFFF                          # 4Gb - (0x100000*0x1000 = 4Gb)
926         .word   0                               # base address = 0
927         .word   0x9200                          # data read/write
928         .word   0x00CF                          # granularity = 4096, 386
929                                                 #  (+5th nibble of limit)
930 gdt_end:
931         .align  4
932         
933         .word   0                               # alignment byte
934 idt_48:
935         .word   0                               # idt limit = 0
936         .word   0, 0                            # idt base = 0L
937
938         .word   0                               # alignment byte
939 gdt_48:
940         .word   gdt_end - gdt - 1               # gdt limit
941         .word   0, 0                            # gdt base (filled in later)
942
943 # Include video setup & detection code
944
945 #include "video.S"
946
947 # Setup signature -- must be last
948 setup_sig1:     .word   SIG1
949 setup_sig2:     .word   SIG2
950
951 # After this point, there is some free space which is used by the video mode
952 # handling code to store the temporary mode table (not used by the kernel).
953
954 modelist:
955
956 .text
957 endtext:
958 .data
959 enddata:
960 .bss
961 endbss: