root/arch/i386/boot/setup.S

/* [previous][next][first][last][top][bottom][index][help] */
   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 ! (Stephen.Rothwell@pd.necisa.oz.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 ! NOTE! These had better be the same as in bootsect.s!
  28 #define __ASSEMBLY__
  29 #include <linux/config.h>
  30 #include <asm/segment.h>
  31 #include <linux/version.h>
  32 #include <linux/compile.h>
  33 
  34 #ifndef SVGA_MODE
  35 #define SVGA_MODE ASK_VGA
  36 #endif
  37 
  38 ! Signature words to ensure LILO loaded us right
  39 #define SIG1    0xAA55
  40 #define SIG2    0x5A5A
  41 
  42 INITSEG  = DEF_INITSEG  ! 0x9000, we move boot here - out of the way
  43 SYSSEG   = DEF_SYSSEG   ! 0x1000, system loaded at 0x10000 (65536).
  44 SETUPSEG = DEF_SETUPSEG ! 0x9020, this is the current segment
  45                         ! ... and the former contents of CS
  46 DELTA_INITSEG = SETUPSEG - INITSEG ! 0x0020
  47 
  48 .globl begtext, begdata, begbss, endtext, enddata, endbss
  49 .text
  50 begtext:
  51 .data
  52 begdata:
  53 .bss
  54 begbss:
  55 .text
  56 
  57 entry start
  58 start:
  59         jmp     start_of_setup
  60 ! ------------------------ start of header --------------------------------
  61 !
  62 ! SETUP-header, must start at CS:2 (old 0x9020:2)
  63 !
  64                 .ascii  "HdrS"          ! Signature for SETUP-header
  65                 .word   0x0200          ! Version number of header format
  66                                         ! (must be >= 0x0105
  67                                         ! else old loadlin-1.5 will fail)
  68 realmode_swtch: .word   0,0             ! default_switch,SETUPSEG
  69 start_sys_seg:  .word   SYSSEG
  70                 .word   kernel_version  ! pointing to kernel version string
  71   ! note: above part of header is compatible with loadlin-1.5 (header v1.5),
  72   !        must not change it
  73 
  74 type_of_loader: .byte   0               ! = 0, old one (LILO, Loadlin,
  75                                         !      Bootlin, SYSLX, bootsect...)
  76                                         ! else it is set by the loader:
  77                                         ! 0xTV: T=0 for LILO
  78                                         !       T=1 for Loadlin
  79                                         !       T=2 for bootsect-loader
  80                                         !       V = version
  81 loadflags:      .byte   0       ! unused bits =0 (reserved for future development)
  82 LOADED_HIGH     = 1             ! bit within loadflags,
  83                                 ! if set, then the kernel is loaded high
  84 setup_move_size: .word  0x8000  ! size to move, when we (setup) are not
  85                                 ! loaded at 0x90000. We will move ourselves
  86                                 ! to 0x90000 then just before jumping into
  87                                 ! the kernel. However, only the loader
  88                                 ! know how much of data behind us also needs
  89                                 ! to be loaded.
  90 code32_start:   .long   0x1000          ! here loaders can put a different
  91                                         ! start address for 32-bit code.
  92                                         !   0x1000 = default for zImage
  93                                         ! 0x100000 = default for big kernel
  94 ramdisk_image:  .long   0       ! address of loaded ramdisk image
  95                                 ! Here the loader (or kernel generator) puts
  96                                 ! the 32-bit address were it loaded the image.
  97                                 ! This only will be interpreted by the kernel.
  98 ramdisk_size:   .long   0       ! its size in bytes
  99 bootsect_kludge:
 100                 .word   bootsect_helper,SETUPSEG
 101 ! ------------------------ end of header ----------------------------------
 102 
 103 start_of_setup:
 104 ! Bootlin depends on this being done early
 105         mov     ax,#0x01500
 106         mov     dl,#0x81
 107         int     0x13
 108 
 109 ! set DS=CS, we know that SETUPSEG == CS at this point
 110         mov     ax,cs           ! aka #SETUPSEG
 111         mov     ds,ax
 112 
 113 ! Check signature at end of setup
 114         cmp     setup_sig1,#SIG1
 115         jne     bad_sig
 116         cmp     setup_sig2,#SIG2
 117         jne     bad_sig
 118         jmp     good_sig1
 119 
 120 ! Routine to print asciiz-string at DS:SI
 121 
 122 prtstr: lodsb
 123         and     al,al
 124         jz      fin
 125         call    prnt1
 126         jmp     prtstr
 127 fin:    ret
 128 
 129 ! Part of above routine, this one just prints ascii al
 130 
 131 prnt1:  push    ax
 132         push    cx
 133         xor     bh,bh
 134         mov     cx,#0x01
 135         mov     ah,#0x0e
 136         int     0x10
 137         pop     cx
 138         pop     ax
 139         ret
 140 
 141 beep:   mov     al,#0x07
 142         jmp     prnt1
 143         
 144 no_sig_mess:    .ascii  "No setup signature found ..."
 145                 db      0x00
 146 
 147 good_sig1:
 148         jmp     good_sig
 149 
 150 ! We now have to find the rest of the setup code/data
 151 bad_sig:
 152         mov     ax,cs           ! aka #SETUPSEG
 153         sub     ax,#DELTA_INITSEG ! aka #INITSEG
 154         mov     ds,ax
 155         xor     bh,bh
 156         mov     bl,[497]        ! get setup sects from boot sector
 157         sub     bx,#4           ! LILO loads 4 sectors of setup
 158         shl     bx,#8           ! convert to words
 159         mov     cx,bx
 160         shr     bx,#3           ! convert to segment
 161         add     bx,#SYSSEG
 162         seg cs
 163         mov     start_sys_seg,bx
 164 
 165 ! Move rest of setup code/data to here
 166         mov     di,#2048        ! four sectors loaded by LILO
 167         sub     si,si
 168         mov     ax,cs           ! aka #SETUPSEG
 169         mov     es,ax
 170         mov     ax,#SYSSEG
 171         mov     ds,ax
 172         rep
 173         movsw
 174 
 175         mov     ax,cs           ! aka #SETUPSEG
 176         mov     ds,ax
 177         cmp     setup_sig1,#SIG1
 178         jne     no_sig
 179         cmp     setup_sig2,#SIG2
 180         jne     no_sig
 181         jmp     good_sig
 182 
 183 no_sig:
 184         lea     si,no_sig_mess
 185         call    prtstr
 186 no_sig_loop:
 187         jmp     no_sig_loop
 188 
 189 good_sig:
 190         mov     ax,cs           ! aka #SETUPSEG
 191         sub     ax,#DELTA_INITSEG ! aka #INITSEG
 192         mov     ds,ax
 193 
 194 ! check if an old loader tries to load a big-kernel
 195         seg cs
 196         test    byte ptr loadflags,#LOADED_HIGH ! have we a big kernel ?
 197         jz      loader_ok       ! NO, no danger even for old loaders
 198                                 ! YES, we have a big-kernel
 199         seg cs
 200         cmp     byte ptr type_of_loader,#0 ! have we one of the new loaders ?
 201         jnz     loader_ok       ! YES, ok
 202                                 ! NO, we have an old loader, must give up
 203         push    cs
 204         pop     ds
 205         lea     si,loader_panic_mess
 206         call    prtstr
 207         jmp     no_sig_loop
 208 loader_panic_mess: 
 209         .ascii  "Wrong loader, giving up..."
 210         db      0
 211 
 212 loader_ok:
 213 ! Get memory size (extended mem, kB)
 214 
 215         mov     ah,#0x88
 216         int     0x15
 217         mov     [2],ax
 218 
 219 ! set the keyboard repeat rate to the max
 220 
 221         mov     ax,#0x0305
 222         xor     bx,bx           ! clear bx
 223         int     0x16
 224 
 225 ! check for EGA/VGA and some config parameters
 226 
 227         mov     ah,#0x12
 228         mov     bl,#0x10
 229         int     0x10
 230         mov     [8],ax
 231         mov     [10],bx
 232         mov     [12],cx
 233         mov     ax,#0x5019
 234         cmp     bl,#0x10
 235         je      novga
 236         mov     ax,#0x1a00      ! Added check for EGA/VGA discrimination
 237         int     0x10
 238         mov     bx,ax
 239         mov     ax,#0x5019
 240         movb    [15],#0         ! by default, no VGA
 241         cmp     bl,#0x1a        ! 1a means VGA, anything else EGA or lower
 242         jne     novga
 243         movb    [15],#1         ! we've detected a VGA
 244         call    chsvga
 245 novga:  mov     [14],al
 246         mov     ah,#0x03        ! read cursor pos
 247         xor     bh,bh           ! clear bh
 248         int     0x10            ! save it in known place, con_init fetches
 249         mov     [0],dx          ! it from 0x90000.
 250         
 251 ! Get video-card data:
 252         
 253         mov     ah,#0x0f
 254         int     0x10
 255         mov     [4],bx          ! bh = display page
 256         mov     [6],ax          ! al = video mode, ah = window width
 257         xor     ax,ax
 258         mov     es,ax           ! Access low memory
 259         seg es
 260         mov     ax,[0x485]      ! POINTS - Height of character matrix
 261         mov     [16],ax
 262 
 263 ! Get hd0 data
 264 
 265         xor     ax,ax           ! clear ax
 266         mov     ds,ax
 267         lds     si,[4*0x41]
 268         mov     ax,cs           ! aka #SETUPSEG
 269         sub     ax,#DELTA_INITSEG ! aka #INITSEG
 270         push    ax
 271         mov     es,ax
 272         mov     di,#0x0080
 273         mov     cx,#0x10
 274         push    cx
 275         cld
 276         rep
 277         movsb
 278 
 279 ! Get hd1 data
 280 
 281         xor     ax,ax           ! clear ax
 282         mov     ds,ax
 283         lds     si,[4*0x46]
 284         pop     cx
 285         pop     es
 286         mov     di,#0x0090
 287         rep
 288         movsb
 289 
 290 ! Check that there IS a hd1 :-)
 291 
 292         mov     ax,#0x01500
 293         mov     dl,#0x81
 294         int     0x13
 295         jc      no_disk1
 296         cmp     ah,#3
 297         je      is_disk1
 298 no_disk1:
 299         mov     ax,cs           ! aka #SETUPSEG
 300         sub     ax,#DELTA_INITSEG ! aka #INITSEG
 301         mov     es,ax
 302         mov     di,#0x0090
 303         mov     cx,#0x10
 304         xor     ax,ax           ! clear ax
 305         cld
 306         rep
 307         stosb
 308 is_disk1:
 309 
 310 ! check for PS/2 pointing device
 311 
 312         mov     ax,cs           ! aka #SETUPSEG
 313         sub     ax,#DELTA_INITSEG ! aka #INITSEG
 314         mov     ds,ax
 315         mov     [0x1ff],#0      ! default is no pointing device
 316         int     0x11            ! int 0x11: equipment determination
 317         test    al,#0x04        ! check if pointing device installed
 318         jz      no_psmouse
 319         mov     [0x1ff],#0xaa   ! device present
 320 no_psmouse:
 321 
 322 #ifdef CONFIG_APM
 323 ! check for APM BIOS
 324                 ! NOTE: DS is pointing to the bootsector
 325                 !
 326         mov     [64],#0         ! version == 0 means no APM BIOS
 327 
 328         mov     ax,#0x05300     ! APM BIOS installation check
 329         xor     bx,bx
 330         int     0x15
 331         jc      done_apm_bios   ! error -> no APM BIOS
 332 
 333         cmp     bx,#0x0504d     ! check for "PM" signature
 334         jne     done_apm_bios   ! no signature -> no APM BIOS
 335 
 336         mov     [64],ax         ! record the APM BIOS version
 337         mov     [76],cx         !       and flags
 338         and     cx,#0x02        ! Is 32 bit supported?
 339         je      done_apm_bios   !       no ...
 340 
 341         mov     ax,#0x05304     ! Disconnect first just in case
 342         xor     bx,bx
 343         int     0x15            ! ignore return code
 344 
 345         mov     ax,#0x05303     ! 32 bit connect
 346         xor     bx,bx
 347         int     0x15
 348         jc      no_32_apm_bios  ! error
 349 
 350         mov     [66],ax         ! BIOS code segment
 351         mov     [68],ebx        ! BIOS entry point offset
 352         mov     [72],cx         ! BIOS 16 bit code segment
 353         mov     [74],dx         ! BIOS data segment
 354         mov     [78],si         ! BIOS code segment length
 355         mov     [80],di         ! BIOS data segment length
 356         jmp     done_apm_bios
 357 
 358 no_32_apm_bios:
 359         and     [76], #0xfffd   ! remove 32 bit support bit
 360 
 361 done_apm_bios:
 362 #endif
 363 
 364 ! now we want to move to protected mode ...
 365 
 366         seg cs
 367         cmp     realmode_swtch,#0
 368         jz      rmodeswtch_normal
 369         seg cs
 370         callf   far * realmode_swtch
 371         jmp     rmodeswtch_end
 372 rmodeswtch_normal:
 373         push    cs
 374         call    default_switch
 375 rmodeswtch_end:
 376 
 377 ! we get the code32 start address and modify the below 'jmpi'
 378 ! (loader may have changed it)
 379         seg cs
 380         mov     eax,code32_start
 381         seg cs
 382         mov     code32,eax
 383 
 384 ! Now we move the system to its rightful place
 385 ! ...but we check, if we have a big-kernel.
 386 ! in this case we *must* not move it ...
 387         seg cs
 388         test    byte ptr loadflags,#LOADED_HIGH
 389         jz      do_move0        ! we have a normal low loaded zImage
 390                                 ! we have a high loaded big kernel
 391         jmp     end_move        ! ... and we skip moving
 392 
 393 do_move0:
 394         mov     ax,#0x100       ! start of destination segment
 395         mov     bp,cs           ! aka #SETUPSEG
 396         sub     bp,#DELTA_INITSEG ! aka #INITSEG
 397         seg cs
 398         mov     bx,start_sys_seg        ! start of source segment
 399         cld                     ! 'direction'=0, movs moves forward
 400 do_move:
 401         mov     es,ax           ! destination segment
 402         inc     ah              ! instead of add ax,#0x100
 403         mov     ds,bx           ! source segment
 404         add     bx,#0x100
 405         sub     di,di
 406         sub     si,si
 407         mov     cx,#0x800
 408         rep
 409         movsw
 410         cmp     bx,bp           ! we assume start_sys_seg > 0x200,
 411                                 ! so we will perhaps read one page more then
 412                                 ! needed, but never overwrite INITSEG because
 413                                 ! destination is minimum one page below source
 414         jb      do_move
 415 
 416 ! then we load the segment descriptors
 417 
 418 end_move:
 419         mov     ax,cs ! aka #SETUPSEG   ! right, forgot this at first. didn't work :-)
 420         mov     ds,ax
 421 
 422 ! If we have our code not at 0x90000, we need to move it there now.
 423 ! We also then need to move the params behind it (commandline)
 424 ! Because we would overwrite the code on the current IP, we move
 425 ! it in two steps, jumping high after the first one.
 426         mov     ax,cs
 427         cmp     ax,#SETUPSEG
 428         je      end_move_self
 429         cli     ! make sure we really have interrupts disabled !
 430                 ! because after this the stack should not be used
 431         sub     ax,#DELTA_INITSEG ! aka #INITSEG
 432         mov     dx,ss
 433         cmp     dx,ax
 434         jb      move_self_1
 435         add     dx,#INITSEG
 436         sub     dx,ax           ! this will be SS after the move
 437 move_self_1:
 438         mov     ds,ax
 439         mov     ax,#INITSEG     ! real INITSEG
 440         mov     es,ax
 441         seg cs
 442         mov     cx,setup_move_size
 443         std             ! we have to move up, so we use direction down
 444                         ! because the areas may overlap
 445         mov     di,cx
 446         dec     di
 447         mov     si,di
 448         sub     cx,#move_self_here+0x200
 449         rep
 450         movsb
 451         jmpi    move_self_here,SETUPSEG ! jump to our final place
 452 move_self_here:
 453         mov     cx,#move_self_here+0x200
 454         rep
 455         movsb
 456         mov     ax,#SETUPSEG
 457         mov     ds,ax
 458         mov     ss,dx
 459                         ! now we are at the right place
 460 end_move_self:
 461 
 462         lidt    idt_48          ! load idt with 0,0
 463         lgdt    gdt_48          ! load gdt with whatever appropriate
 464 
 465 ! that was painless, now we enable A20
 466 
 467         call    empty_8042
 468         mov     al,#0xD1                ! command write
 469         out     #0x64,al
 470         call    empty_8042
 471         mov     al,#0xDF                ! A20 on
 472         out     #0x60,al
 473         call    empty_8042
 474 
 475 ! make sure any possible coprocessor is properly reset..
 476 
 477         xor     ax,ax
 478         out     #0xf0,al
 479         call    delay
 480         out     #0xf1,al
 481         call    delay
 482 
 483 ! well, that went ok, I hope. Now we have to reprogram the interrupts :-(
 484 ! we put them right after the intel-reserved hardware interrupts, at
 485 ! int 0x20-0x2F. There they won't mess up anything. Sadly IBM really
 486 ! messed this up with the original PC, and they haven't been able to
 487 ! rectify it afterwards. Thus the bios puts interrupts at 0x08-0x0f,
 488 ! which is used for the internal hardware interrupts as well. We just
 489 ! have to reprogram the 8259's, and it isn't fun.
 490 
 491         mov     al,#0x11                ! initialization sequence
 492         out     #0x20,al                ! send it to 8259A-1
 493         call    delay
 494         out     #0xA0,al                ! and to 8259A-2
 495         call    delay
 496         mov     al,#0x20                ! start of hardware int's (0x20)
 497         out     #0x21,al
 498         call    delay
 499         mov     al,#0x28                ! start of hardware int's 2 (0x28)
 500         out     #0xA1,al
 501         call    delay
 502         mov     al,#0x04                ! 8259-1 is master
 503         out     #0x21,al
 504         call    delay
 505         mov     al,#0x02                ! 8259-2 is slave
 506         out     #0xA1,al
 507         call    delay
 508         mov     al,#0x01                ! 8086 mode for both
 509         out     #0x21,al
 510         call    delay
 511         out     #0xA1,al
 512         call    delay
 513         mov     al,#0xFF                ! mask off all interrupts for now
 514         out     #0xA1,al
 515         call    delay
 516         mov     al,#0xFB                ! mask all irq's but irq2 which
 517         out     #0x21,al                ! is cascaded
 518 
 519 ! well, that certainly wasn't fun :-(. Hopefully it works, and we don't
 520 ! need no steenking BIOS anyway (except for the initial loading :-).
 521 ! The BIOS-routine wants lots of unnecessary data, and it's less
 522 ! "interesting" anyway. This is how REAL programmers do it.
 523 !
 524 ! Well, now's the time to actually move into protected mode. To make
 525 ! things as simple as possible, we do no register set-up or anything,
 526 ! we let the gnu-compiled 32-bit programs do that. We just jump to
 527 ! absolute address 0x1000 (or the loader supplied one),
 528 ! in 32-bit protected mode.
 529 !
 530 ! Note that the short jump isn't strictly needed, although there are
 531 ! reasons why it might be a good idea. It won't hurt in any case.
 532 !
 533         xor     ax,ax
 534         inc     ax              ! protected mode (PE) bit
 535         lmsw    ax              ! This is it!
 536         jmp     flush_instr
 537 flush_instr:
 538         mov     bx,#0           ! Flag to indicate a boot
 539 
 540 ! NOTE: For high loaded big kernels we need a
 541 !       jmpi    0x100000,KERNEL_CS
 542 !
 543 !       but we yet haven't reloaded the CS register, so the default size 
 544 !       of the target offset still is 16 bit.
 545 !       However, using an operant prefix (0x66), the CPU will properly
 546 !       take our 48 bit far pointer. (INTeL 80386 Programmer's Reference
 547 !       Manual, Mixing 16-bit and 32-bit code, page 16-6)
 548         db      0x66,0xea       ! prefix + jmpi-opcode
 549 code32: dd      0x1000          ! will be set to 0x100000 for big kernels
 550         dw      KERNEL_CS
 551 
 552 
 553 kernel_version: .ascii  UTS_RELEASE
 554                 .ascii  " ("
 555                 .ascii  LINUX_COMPILE_BY
 556                 .ascii  "@"
 557                 .ascii  LINUX_COMPILE_HOST
 558                 .ascii  ") "
 559                 .ascii  UTS_VERSION
 560                 db      0
 561 
 562 ! This is the default real mode switch routine.
 563 ! to be called just before protected mode transition
 564 
 565 default_switch:
 566         cli                     ! no interrupts allowed !
 567         mov     al,#0x80        ! disable NMI for the bootup sequence
 568         out     #0x70,al
 569         retf
 570 
 571 ! This routine only gets called, if we get loaded by the simple
 572 ! bootsect loader _and_ have a bzImage to load.
 573 ! Because there is no place left in the 512 bytes of the boot sector,
 574 ! we must emigrate to code space here.
 575 !
 576 bootsect_helper:
 577         seg cs
 578         cmp     word ptr bootsect_es,#0
 579         jnz     bootsect_second
 580         seg cs
 581         mov     byte ptr type_of_loader,#0x20
 582         mov     ax,es
 583         shr     ax,#4
 584         seg     cs
 585         mov     byte ptr bootsect_src_base+2,ah
 586         mov     ax,es
 587         seg cs
 588         mov     bootsect_es,ax
 589         sub     ax,#SYSSEG
 590         retf                    ! nothing else to do for now
 591 bootsect_second:
 592         push    cx
 593         push    si
 594         push    bx
 595         test    bx,bx   ! 64K full ?
 596         jne     bootsect_ex
 597         mov     cx,#0x8000      ! full 64K move, INT15 moves words
 598         push    cs
 599         pop     es
 600         mov     si,#bootsect_gdt
 601         mov     ax,#0x8700
 602         int     0x15
 603         jc      bootsect_panic  ! this, if INT15 fails
 604         seg cs
 605         mov     es,bootsect_es  ! we reset es to always point to 0x10000
 606         seg cs
 607         inc     byte ptr bootsect_dst_base+2
 608 bootsect_ex:
 609         seg cs
 610         mov     ah, byte ptr bootsect_dst_base+2
 611         shl     ah,4    ! we now have the number of moved frames in ax
 612         xor     al,al
 613         pop     bx
 614         pop     si
 615         pop     cx
 616         retf
 617 
 618 bootsect_gdt:
 619         .word   0,0,0,0
 620         .word   0,0,0,0
 621 bootsect_src:
 622         .word   0xffff
 623 bootsect_src_base:
 624         .byte   0,0,1                   ! base = 0x010000
 625         .byte   0x93                    ! typbyte
 626         .word   0                       ! limit16,base24 =0
 627 bootsect_dst:
 628         .word   0xffff
 629 bootsect_dst_base:
 630         .byte   0,0,0x10                ! base = 0x100000
 631         .byte   0x93                    ! typbyte
 632         .word   0                       ! limit16,base24 =0
 633         .word   0,0,0,0                 ! BIOS CS
 634         .word   0,0,0,0                 ! BIOS DS
 635 bootsect_es:
 636         .word   0
 637 
 638 bootsect_panic:
 639         push    cs
 640         pop     ds
 641         cld
 642         lea     si,bootsect_panic_mess
 643         call    prtstr
 644 bootsect_panic_loop:
 645         jmp     bootsect_panic_loop
 646 bootsect_panic_mess:
 647         .ascii  "INT15 refuses to access high mem, giving up..."
 648         db      0
 649 
 650 ! This routine checks that the keyboard command queue is empty
 651 ! (after emptying the output buffers)
 652 !
 653 ! No timeout is used - if this hangs there is something wrong with
 654 ! the machine, and we probably couldn't proceed anyway.
 655 empty_8042:
 656         call    delay
 657         in      al,#0x64        ! 8042 status port
 658         test    al,#1           ! output buffer?
 659         jz      no_output
 660         call    delay
 661         in      al,#0x60        ! read it
 662         jmp     empty_8042
 663 no_output:
 664         test    al,#2           ! is input buffer full?
 665         jnz     empty_8042      ! yes - loop
 666         ret
 667 !
 668 ! Read a key and return the (US-)ascii code in al, scan code in ah
 669 !
 670 getkey:
 671         xor     ah,ah
 672         int     0x16
 673         ret
 674 
 675 !
 676 ! Read a key with a timeout of 30 seconds. The cmos clock is used to get
 677 ! the time.
 678 !
 679 getkt:
 680         call    gettime
 681         add     al,#30          ! wait 30 seconds
 682         cmp     al,#60
 683         jl      lminute
 684         sub     al,#60
 685 lminute:
 686         mov     cl,al
 687 again:  mov     ah,#0x01
 688         int     0x16
 689         jnz     getkey          ! key pressed, so get it
 690         call    gettime
 691         cmp     al,cl
 692         jne     again
 693         mov     al,#0x20        ! timeout, return default char `space'
 694         ret
 695 
 696 !
 697 ! Flush the keyboard buffer
 698 !
 699 flush:  mov     ah,#0x01
 700         int     0x16
 701         jz      empty
 702         xor     ah,ah
 703         int     0x16
 704         jmp     flush
 705 empty:  ret
 706 
 707 !
 708 ! Read the cmos clock. Return the seconds in al
 709 !
 710 gettime:
 711         push    cx
 712         mov     ah,#0x02
 713         int     0x1a
 714         mov     al,dh                   ! dh contains the seconds
 715         and     al,#0x0f
 716         mov     ah,dh
 717         mov     cl,#0x04
 718         shr     ah,cl
 719         aad
 720         pop     cx
 721         ret
 722 
 723 !
 724 ! Delay is needed after doing i/o
 725 !
 726 delay:
 727         .word   0x00eb                  ! jmp $+2
 728         ret
 729 
 730 ! Routine trying to recognize type of SVGA-board present (if any)
 731 ! and if it recognize one gives the choices of resolution it offers.
 732 ! If one is found the resolution chosen is given by al,ah (rows,cols).
 733 
 734 chsvga: cld
 735         push    ds
 736         push    cs
 737         mov     ax,[0x01fa]
 738         pop     ds
 739         mov     modesave,ax
 740         mov     ax,#0xc000
 741         mov     es,ax
 742         mov     ax,modesave
 743         cmp     ax,#NORMAL_VGA
 744         je      defvga
 745         cmp     ax,#EXTENDED_VGA
 746         je      vga50
 747         cmp     ax,#ASK_VGA
 748         jne     svga
 749         lea     si,msg1
 750         call    prtstr
 751         call    flush
 752 nokey:  call    getkt
 753         cmp     al,#0x0d                ! enter ?
 754         je      svga                    ! yes - svga selection
 755         cmp     al,#0x20                ! space ?
 756         je      defvga                  ! no - repeat
 757         call    beep
 758         jmp     nokey
 759 defvga: mov     ax,#0x5019
 760         pop     ds
 761         ret
 762 /* extended vga mode: 80x50 */
 763 vga50:
 764         mov     ax,#0x1112
 765         xor     bl,bl
 766         int     0x10            ! use 8x8 font set (50 lines on VGA)
 767         mov     ax,#0x1200
 768         mov     bl,#0x20
 769         int     0x10            ! use alternate print screen
 770         mov     ax,#0x1201
 771         mov     bl,#0x34
 772         int     0x10            ! turn off cursor emulation
 773         mov     ah,#0x01
 774         mov     cx,#0x0607
 775         int     0x10            ! turn on cursor (scan lines 6 to 7)
 776         pop     ds
 777         mov     ax,#0x5032      ! return 80x50
 778         ret
 779 /* extended vga mode: 80x28 */
 780 vga28:
 781         pop     ax              ! clean the stack
 782         mov     ax,#0x1111
 783         xor     bl,bl
 784         int     0x10            ! use 9x14 fontset (28 lines on VGA)
 785         mov     ah, #0x01
 786         mov     cx,#0x0b0c
 787         int     0x10            ! turn on cursor (scan lines 11 to 12)
 788         pop     ds
 789         mov     ax,#0x501c      ! return 80x28
 790         ret
 791 /* svga modes */
 792 !
 793 !       test for presence of an S3 VGA chip. The algorithm was taken
 794 !       from the SuperProbe package of XFree86 1.2.1
 795 !       report bugs to Christoph.Niemann@linux.org
 796 !
 797 svga:   cld
 798         mov     cx,#0x0f35      ! we store some constants in cl/ch
 799         mov     dx,#0x03d4
 800         movb    al,#0x38
 801         call    inidx
 802         mov     bh,al           ! store current value of CRT-register 0x38
 803         mov     ax,#0x0038
 804         call    outidx          ! disable writing to special regs
 805         movb    al,cl           ! check whether we can write special reg 0x35
 806         call    inidx
 807         movb    bl,al           ! save the current value of CRT reg 0x35
 808         andb    al,#0xf0        ! clear bits 0-3
 809         movb    ah,al
 810         movb    al,cl           ! and write it to CRT reg 0x35
 811         call    outidx
 812         call    inidx           ! now read it back
 813         andb    al,ch           ! clear the upper 4 bits
 814         jz      s3_2            ! the first test failed. But we have a
 815         movb    ah,bl           ! second chance
 816         mov     al,cl
 817         call    outidx
 818         jmp     s3_1            ! do the other tests
 819 s3_2:   mov     ax,cx           ! load ah with 0xf and al with 0x35
 820         orb     ah,bl           ! set the upper 4 bits of ah with the orig value
 821         call    outidx          ! write ...
 822         call    inidx           ! ... and reread 
 823         andb    al,cl           ! turn off the upper 4 bits
 824         push    ax
 825         movb    ah,bl           ! restore old value in register 0x35
 826         movb    al,cl
 827         call    outidx
 828         pop     ax
 829         cmp     al,ch           ! setting lower 4 bits was successful => bad
 830         je      no_s3           ! writing is allowed => this is not an S3
 831 s3_1:   mov     ax,#0x4838      ! allow writing to special regs by putting
 832         call    outidx          ! magic number into CRT-register 0x38
 833         movb    al,cl           ! check whether we can write special reg 0x35
 834         call    inidx
 835         movb    bl,al
 836         andb    al,#0xf0
 837         movb    ah,al
 838         movb    al,cl
 839         call    outidx
 840         call    inidx
 841         andb    al,ch
 842         jnz     no_s3           ! no, we can't write => no S3
 843         mov     ax,cx
 844         orb     ah,bl
 845         call    outidx
 846         call    inidx
 847         andb    al,ch
 848         push    ax
 849         movb    ah,bl           ! restore old value in register 0x35
 850         movb    al,cl
 851         call    outidx
 852         pop     ax
 853         cmp     al,ch
 854         jne     no_s31          ! writing not possible => no S3
 855         movb    al,#0x30
 856         call    inidx           ! now get the S3 id ...
 857         lea     di,idS3
 858         mov     cx,#0x10
 859         repne
 860         scasb
 861         je      no_s31
 862         lea     si,dsc_S3       ! table of descriptions of video modes for BIOS
 863         lea     di,mo_S3        ! table of sizes of video modes for my BIOS
 864         movb    ah,bh
 865         movb    al,#0x38
 866         call    outidx          ! restore old value of CRT register 0x38
 867         br      selmod          ! go ask for video mode
 868 no_s3:  movb    al,#0x35        ! restore CRT register 0x35
 869         movb    ah,bl
 870         call    outidx
 871 no_s31: movb    ah,bh
 872         movb    al,#0x38
 873         call    outidx          ! restore old value of CRT register 0x38
 874 
 875         lea     si,idati                ! Check ATI 'clues'
 876         mov     di,#0x31
 877         mov     cx,#0x09
 878         repe
 879         cmpsb
 880         jne     noati
 881         lea     si,dscati
 882         lea     di,moati
 883         br      selmod
 884 noati:  mov     ax,#0x200f              ! Check Ahead 'clues'
 885         mov     dx,#0x3ce
 886         out     dx,ax
 887         inc     dx
 888         in      al,dx
 889         cmp     al,#0x20
 890         je      isahed
 891         cmp     al,#0x21
 892         jne     noahed
 893 isahed: lea     si,dscahead
 894         lea     di,moahead
 895         br      selmod
 896 noahed: mov     dx,#0x3c3               ! Check Chips & Tech. 'clues'
 897         in      al,dx
 898         or      al,#0x10
 899         out     dx,al
 900         mov     dx,#0x104               
 901         in      al,dx
 902         mov     bl,al
 903         mov     dx,#0x3c3
 904         in      al,dx
 905         and     al,#0xef
 906         out     dx,al
 907         cmp     bl,[idcandt]
 908         jne     nocant
 909         lea     si,dsccandt
 910         lea     di,mocandt
 911         br      selmod
 912 nocant: mov     dx,#0x3d4               ! Check Cirrus 'clues'
 913         mov     al,#0x0c
 914         out     dx,al
 915         inc     dx
 916         in      al,dx
 917         mov     bl,al
 918         xor     al,al
 919         out     dx,al
 920         dec     dx
 921         mov     al,#0x1f
 922         out     dx,al
 923         inc     dx
 924         in      al,dx
 925         mov     bh,al
 926         xor     ah,ah
 927         shl     al,#4
 928         mov     cx,ax
 929         mov     al,bh
 930         shr     al,#4
 931         add     cx,ax
 932         shl     cx,#8
 933         add     cx,#6
 934         mov     ax,cx
 935         mov     dx,#0x3c4
 936         out     dx,ax
 937         inc     dx
 938         in      al,dx
 939         and     al,al
 940         jnz     nocirr
 941         mov     al,bh
 942         out     dx,al
 943         in      al,dx
 944         cmp     al,#0x01
 945         jne     nocirr
 946         call    rst3d4  
 947         lea     si,dsccirrus
 948         lea     di,mocirrus
 949         br      selmod
 950 rst3d4: mov     dx,#0x3d4
 951         mov     al,bl
 952         xor     ah,ah
 953         shl     ax,#8
 954         add     ax,#0x0c
 955         out     dx,ax
 956         ret     
 957 nocirr: call    rst3d4                  ! Check Everex 'clues'
 958         mov     ax,#0x7000
 959         xor     bx,bx
 960         int     0x10
 961         cmp     al,#0x70
 962         jne     noevrx
 963         shr     dx,#4
 964         cmp     dx,#0x678
 965         je      istrid
 966         cmp     dx,#0x236
 967         je      istrid
 968         lea     si,dsceverex
 969         lea     di,moeverex
 970         br      selmod
 971 istrid: lea     cx,ev2tri
 972         jmp     cx
 973 noevrx: lea     si,idgenoa              ! Check Genoa 'clues'
 974         xor     ax,ax
 975         seg es
 976         mov     al,[0x37]
 977         mov     di,ax
 978         mov     cx,#0x04
 979         dec     si
 980         dec     di
 981 l1:     inc     si
 982         inc     di
 983         mov     al,(si)
 984         test    al,al
 985         jz      l2
 986         seg es
 987         cmp     al,(di)
 988 l2:     loope   l1
 989         cmp     cx,#0x00
 990         jne     nogen
 991         lea     si,dscgenoa
 992         lea     di,mogenoa
 993         br      selmod
 994 nogen:  cld
 995         lea     si,idoakvga
 996         mov     di,#0x08
 997         mov     cx,#0x08
 998         repe
 999         cmpsb
1000         jne     nooak
1001         lea     si,dscoakvga
1002         lea     di,mooakvga
1003         br      selmod
1004 nooak:  cld
1005         lea     si,idparadise           ! Check Paradise 'clues'
1006         mov     di,#0x7d
1007         mov     cx,#0x04
1008         repe
1009         cmpsb
1010         jne     nopara
1011         lea     si,dscparadise
1012         lea     di,moparadise
1013         br      selmod
1014 nopara: mov     dx,#0x3c4               ! Check Trident 'clues'
1015         mov     al,#0x0e
1016         out     dx,al
1017         inc     dx
1018         in      al,dx
1019         xchg    ah,al
1020         xor     al,al
1021         out     dx,al
1022         in      al,dx
1023         xchg    al,ah
1024         mov     bl,al           ! Strange thing ... in the book this wasn't
1025         and     bl,#0x02        ! necessary but it worked on my card which
1026         jz      setb2           ! is a trident. Without it the screen goes
1027         and     al,#0xfd        ! blurred ...
1028         jmp     clrb2           !
1029 setb2:  or      al,#0x02        !
1030 clrb2:  out     dx,al
1031         and     ah,#0x0f
1032         cmp     ah,#0x02
1033         jne     notrid
1034 ev2tri: lea     si,dsctrident
1035         lea     di,motrident
1036         jmp     selmod
1037 notrid: mov     dx,#0x3cd               ! Check Tseng 'clues'
1038         in      al,dx                   ! Could things be this simple ! :-)
1039         mov     bl,al
1040         mov     al,#0x55
1041         out     dx,al
1042         in      al,dx
1043         mov     ah,al
1044         mov     al,bl
1045         out     dx,al
1046         cmp     ah,#0x55
1047         jne     notsen
1048         lea     si,dsctseng
1049         lea     di,motseng
1050         jmp     selmod
1051 notsen: mov     dx,#0x3cc               ! Check Video7 'clues'
1052         in      al,dx
1053         mov     dx,#0x3b4
1054         and     al,#0x01
1055         jz      even7
1056         mov     dx,#0x3d4
1057 even7:  mov     al,#0x0c
1058         out     dx,al
1059         inc     dx
1060         in      al,dx
1061         mov     bl,al
1062         mov     al,#0x55
1063         out     dx,al
1064         in      al,dx
1065         dec     dx
1066         mov     al,#0x1f
1067         out     dx,al
1068         inc     dx
1069         in      al,dx
1070         mov     bh,al
1071         dec     dx
1072         mov     al,#0x0c
1073         out     dx,al
1074         inc     dx
1075         mov     al,bl
1076         out     dx,al
1077         mov     al,#0x55
1078         xor     al,#0xea
1079         cmp     al,bh
1080         jne     novid7
1081         lea     si,dscvideo7
1082         lea     di,movideo7
1083         jmp     selmod
1084 novid7: lea     si,dsunknown
1085         lea     di,mounknown
1086 selmod: xor     cx,cx
1087         mov     cl,(di)
1088         mov     ax,modesave
1089         cmp     ax,#ASK_VGA
1090         je      askmod
1091         cmp     ax,#NORMAL_VGA
1092         je      askmod
1093         cmp     al,cl
1094         jl      gotmode
1095         push    si
1096         lea     si,msg4
1097         call    prtstr
1098         pop     si
1099 askmod: push    si
1100         lea     si,msg2
1101         call    prtstr
1102         pop     si
1103         push    si
1104         push    cx
1105 tbl:    pop     bx
1106         push    bx
1107         mov     al,bl
1108         sub     al,cl
1109         call    modepr
1110         lodsw
1111         xchg    al,ah
1112         call    dprnt
1113         xchg    ah,al
1114         push    ax
1115         mov     al,#0x78
1116         call    prnt1
1117         pop     ax
1118         call    dprnt
1119         push    si
1120         lea     si,crlf         ! print CR+LF
1121         call    prtstr
1122         pop     si
1123         loop    tbl
1124         pop     cx
1125         lea     si,msg3
1126         call    prtstr
1127         pop     si
1128         add     cl,#0x30
1129         jmp     nonum
1130 nonumb: call    beep
1131 nonum:  call    getkey
1132         cmp     al,#0x30        ! ascii `0'
1133         jb      nonumb
1134         cmp     al,#0x3a        ! ascii `9'
1135         jbe     number
1136         cmp     al,#0x61        ! ascii `a'
1137         jb      nonumb
1138         cmp     al,#0x7a        ! ascii `z'
1139         ja      nonumb
1140         sub     al,#0x27
1141         cmp     al,cl
1142         jae     nonumb
1143         sub     al,#0x30
1144         jmp     gotmode
1145 number: cmp     al,cl
1146         jae     nonumb
1147         sub     al,#0x30
1148 gotmode:        xor     ah,ah
1149         or      al,al
1150         beq     vga50
1151         push    ax
1152         dec     ax
1153         beq     vga28
1154         add     di,ax
1155         mov     al,(di)
1156         int     0x10
1157         pop     ax
1158         shl     ax,#1
1159         add     si,ax
1160         lodsw
1161         pop     ds
1162         ret
1163 
1164 ! Routine to write al into a VGA-register that is
1165 ! accessed via an index register
1166 !
1167 ! dx contains the address of the index register
1168 ! al contains the index
1169 ! ah contains the value to write to the data register (dx + 1)
1170 !
1171 ! no registers are changed
1172 
1173 outidx: out     dx,al
1174         push    ax
1175         mov     al,ah
1176         inc     dx
1177         out     dx,al
1178         dec     dx
1179         pop     ax
1180         ret
1181 inidx:  out     dx,al
1182         inc     dx
1183         in      al,dx
1184         dec     dx
1185         ret
1186 
1187 ! Routine to print a decimal value on screen, the value to be
1188 ! printed is put in al (i.e 0-255). 
1189 
1190 dprnt:  push    ax
1191         push    cx
1192         xor     ah,ah           ! Clear ah
1193         mov     cl,#0x0a
1194         idiv    cl
1195         cmp     al,#0x09
1196         jbe     lt100
1197         call    dprnt
1198         jmp     skip10
1199 lt100:  add     al,#0x30
1200         call    prnt1
1201 skip10: mov     al,ah
1202         add     al,#0x30
1203         call    prnt1   
1204         pop     cx
1205         pop     ax
1206         ret
1207 
1208 !
1209 ! Routine to print the mode number key on screen. Mode numbers
1210 ! 0-9 print the ascii values `0' to '9', 10-35 are represented by
1211 ! the letters `a' to `z'. This routine prints some spaces around the
1212 ! mode no.
1213 !
1214 
1215 modepr: push    ax
1216         cmp     al,#0x0a
1217         jb      digit           ! Here is no check for number > 35
1218         add     al,#0x27
1219 digit:  add     al,#0x30
1220         mov     modenr, al
1221         push    si
1222         lea     si, modestring
1223         call    prtstr
1224         pop     si
1225         pop     ax
1226         ret
1227 
1228 gdt:
1229         .word   0,0,0,0         ! dummy
1230 
1231         .word   0,0,0,0         ! unused
1232 
1233         .word   0xFFFF          ! 4Gb - (0x100000*0x1000 = 4Gb)
1234         .word   0x0000          ! base address=0
1235         .word   0x9A00          ! code read/exec
1236         .word   0x00CF          ! granularity=4096, 386 (+5th nibble of limit)
1237 
1238         .word   0xFFFF          ! 4Gb - (0x100000*0x1000 = 4Gb)
1239         .word   0x0000          ! base address=0
1240         .word   0x9200          ! data read/write
1241         .word   0x00CF          ! granularity=4096, 386 (+5th nibble of limit)
1242 
1243 idt_48:
1244         .word   0                       ! idt limit=0
1245         .word   0,0                     ! idt base=0L
1246 
1247 gdt_48:
1248         .word   0x800           ! gdt limit=2048, 256 GDT entries
1249         .word   512+gdt,0x9     ! gdt base = 0X9xxxx
1250 
1251 msg1:           .ascii  "Press <RETURN> to see SVGA-modes available, <SPACE> to continue or wait 30 secs."
1252                 db      0x0d, 0x0a, 0x0a, 0x00
1253 msg2:           .ascii  "Mode:  COLSxROWS:"
1254                 db      0x0d, 0x0a, 0x0a, 0x00
1255 msg3:           db      0x0d, 0x0a
1256                 .ascii  "Choose mode by pressing the corresponding number or letter."
1257 crlf:           db      0x0d, 0x0a, 0x00
1258 msg4:           .ascii  "You passed an undefined mode number to setup. Please choose a new mode."
1259                 db      0x0d, 0x0a, 0x0a, 0x07, 0x00
1260 modestring:     .ascii  "   "
1261 modenr:         db      0x00    ! mode number
1262                 .ascii  ":    "
1263                 db      0x00
1264                 
1265 idati:          .ascii  "761295520"
1266 idcandt:        .byte   0xa5
1267 idgenoa:        .byte   0x77, 0x00, 0x99, 0x66
1268 idparadise:     .ascii  "VGA="
1269 idoakvga:       .ascii  "OAK VGA "
1270 idS3:           .byte   0x81, 0x82, 0x90, 0x91, 0x92, 0x93, 0x94, 0x95
1271                 .byte   0xa0, 0xa1, 0xa2, 0xa3, 0xa4, 0xa5, 0xa8, 0xb0
1272 
1273 ! Manufacturer:   Numofmodes+2: Mode:
1274 ! Number of modes is the number of chip-specific svga modes plus the extended
1275 ! modes available on any vga (currently 2)
1276 
1277 moati:          .byte   0x06,   0x23, 0x33, 0x22, 0x21
1278 moahead:        .byte   0x07,   0x22, 0x23, 0x24, 0x2f, 0x34
1279 mocandt:        .byte   0x04,   0x60, 0x61
1280 mocirrus:       .byte   0x06,   0x1f, 0x20, 0x22, 0x31
1281 moeverex:       .byte   0x0c,   0x03, 0x04, 0x07, 0x08, 0x0a, 0x0b, 0x16, 0x18, 0x21, 0x40
1282 mogenoa:        .byte   0x0c,   0x58, 0x5a, 0x60, 0x61, 0x62, 0x63, 0x64, 0x72, 0x74, 0x78
1283 moparadise:     .byte   0x04,   0x55, 0x54
1284 motrident:      .byte   0x09,   0x50, 0x51, 0x52, 0x57, 0x58, 0x59, 0x5a
1285 motseng:        .byte   0x07,   0x26, 0x2a, 0x23, 0x24, 0x22
1286 movideo7:       .byte   0x08,   0x40, 0x43, 0x44, 0x41, 0x42, 0x45
1287 mooakvga:       .byte   0x08,   0x00, 0x07, 0x4e, 0x4f, 0x50, 0x51
1288 mo_S3:          .byte   0x04,   0x54, 0x55
1289 mounknown:      .byte   0x02
1290 
1291 !                       msb = Cols lsb = Rows:
1292 ! The first two modes are standard vga modes available on any vga.
1293 ! mode 0 is 80x50 and mode 1 is 80x28
1294 
1295 dscati:         .word   0x5032, 0x501c, 0x8419, 0x842c, 0x641e, 0x6419
1296 dscahead:       .word   0x5032, 0x501c, 0x842c, 0x8419, 0x841c, 0xa032, 0x5042
1297 dsccandt:       .word   0x5032, 0x501c, 0x8419, 0x8432
1298 dsccirrus:      .word   0x5032, 0x501c, 0x8419, 0x842c, 0x841e, 0x6425
1299 dsceverex:      .word   0x5032, 0x501c, 0x5022, 0x503c, 0x642b, 0x644b, 0x8419, 0x842c, 0x501e, 0x641b, 0xa040, 0x841e
1300 dscgenoa:       .word   0x5032, 0x501c, 0x5020, 0x642a, 0x8419, 0x841d, 0x8420, 0x842c, 0x843c, 0x503c, 0x5042, 0x644b
1301 dscparadise:    .word   0x5032, 0x501c, 0x8419, 0x842c
1302 dsctrident:     .word   0x5032, 0x501c, 0x501e, 0x502b, 0x503c, 0x8419, 0x841e, 0x842b, 0x843c
1303 dsctseng:       .word   0x5032, 0x501c, 0x503c, 0x6428, 0x8419, 0x841c, 0x842c
1304 dscvideo7:      .word   0x5032, 0x501c, 0x502b, 0x503c, 0x643c, 0x8419, 0x842c, 0x841c
1305 dscoakvga:      .word   0x5032, 0x501c, 0x2819, 0x5019, 0x503c, 0x843c, 0x8419, 0x842b
1306 dsc_S3:         .word   0x5032, 0x501c, 0x842b, 0x8419
1307 dsunknown:      .word   0x5032, 0x501c
1308 modesave:       .word   SVGA_MODE
1309 
1310 ! This must be last
1311 setup_sig1:     .word   SIG1
1312 setup_sig2:     .word   SIG2
1313 
1314 .text
1315 endtext:
1316 .data
1317 enddata:
1318 .bss
1319 endbss:

/* [previous][next][first][last][top][bottom][index][help] */