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 ! Video handling moved to video.S by Martin Mares, March 1996
  28 ! <mj@k332.feld.cvut.cz>
  29 
  30 ! NOTE! These had better be the same as in bootsect.s!
  31 #define __ASSEMBLY__
  32 #include <linux/config.h>
  33 #include <asm/segment.h>
  34 #include <linux/version.h>
  35 #include <linux/compile.h>
  36 
  37 ! Signature words to ensure LILO loaded us right
  38 #define SIG1    0xAA55
  39 #define SIG2    0x5A5A
  40 
  41 INITSEG  = DEF_INITSEG  ! 0x9000, we move boot here - out of the way
  42 SYSSEG   = DEF_SYSSEG   ! 0x1000, system loaded at 0x10000 (65536).
  43 SETUPSEG = DEF_SETUPSEG ! 0x9020, this is the current segment
  44                         ! ... and the former contents of CS
  45 DELTA_INITSEG = SETUPSEG - INITSEG ! 0x0020
  46 
  47 .globl begtext, begdata, begbss, endtext, enddata, endbss
  48 .text
  49 begtext:
  50 .data
  51 begdata:
  52 .bss
  53 begbss:
  54 .text
  55 
  56 entry start
  57 start:
  58         jmp     start_of_setup
  59 ! ------------------------ start of header --------------------------------
  60 !
  61 ! SETUP-header, must start at CS:2 (old 0x9020:2)
  62 !
  63                 .ascii  "HdrS"          ! Signature for SETUP-header
  64                 .word   0x0201          ! Version number of header format
  65                                         ! (must be >= 0x0105
  66                                         ! else old loadlin-1.5 will fail)
  67 realmode_swtch: .word   0,0             ! default_switch,SETUPSEG
  68 start_sys_seg:  .word   SYSSEG
  69                 .word   kernel_version  ! pointing to kernel version string
  70   ! note: above part of header is compatible with loadlin-1.5 (header v1.5),
  71   !        must not change it
  72 
  73 type_of_loader: .byte   0               ! = 0, old one (LILO, Loadlin,
  74                                         !      Bootlin, SYSLX, bootsect...)
  75                                         ! else it is set by the loader:
  76                                         ! 0xTV: T=0 for LILO
  77                                         !       T=1 for Loadlin
  78                                         !       T=2 for bootsect-loader
  79                                         !       T=3 for SYSLX
  80                                         !       T=4 for ETHERBOOT
  81                                         !       V = version
  82 loadflags:      .byte   0       ! unused bits =0 (reserved for future development)
  83 LOADED_HIGH     = 1             ! bit within loadflags,
  84                                 ! if set, then the kernel is loaded high
  85 CAN_USE_HEAP    = 0x80          ! if set, the loader also has set heap_end_ptr
  86                                 ! to tell how much space behind setup.S
  87                                 | can be used for heap purposes.
  88                                 ! Only the loader knows what is free!
  89 setup_move_size: .word  0x8000  ! size to move, when we (setup) are not
  90                                 ! loaded at 0x90000. We will move ourselves
  91                                 ! to 0x90000 then just before jumping into
  92                                 ! the kernel. However, only the loader
  93                                 ! know how much of data behind us also needs
  94                                 ! to be loaded.
  95 code32_start:   .long   0x1000          ! here loaders can put a different
  96                                         ! start address for 32-bit code.
  97                                         !   0x1000 = default for zImage
  98                                         ! 0x100000 = default for big kernel
  99 ramdisk_image:  .long   0       ! address of loaded ramdisk image
 100                                 ! Here the loader (or kernel generator) puts
 101                                 ! the 32-bit address were it loaded the image.
 102                                 ! This only will be interpreted by the kernel.
 103 ramdisk_size:   .long   0       ! its size in bytes
 104 bootsect_kludge:
 105                 .word   bootsect_helper,SETUPSEG
 106 heap_end_ptr:   .word   modelist+1024   ! space from here (exclusive) down to
 107                                 ! end of setup code can be used by setup
 108                                 ! for local heap purposes.
 109 ! ------------------------ end of header ----------------------------------
 110 
 111 start_of_setup:
 112 ! Bootlin depends on this being done early
 113         mov     ax,#0x01500
 114         mov     dl,#0x81
 115         int     0x13
 116 
 117 #ifdef SAFE_RESET_DISK_CONTROLLER
 118 ! Reset the disk controller.
 119         mov     ax,#0x0000
 120         mov     dl,#0x80
 121         int     0x13
 122 #endif
 123 
 124 ! set DS=CS, we know that SETUPSEG == CS at this point
 125         mov     ax,cs           ! aka #SETUPSEG
 126         mov     ds,ax
 127 
 128 ! Check signature at end of setup
 129         cmp     setup_sig1,#SIG1
 130         jne     bad_sig
 131         cmp     setup_sig2,#SIG2
 132         jne     bad_sig
 133         jmp     good_sig1
 134 
 135 ! Routine to print asciiz-string at DS:SI
 136 
 137 prtstr: lodsb
 138         and     al,al
 139         jz      fin
 140         call    prtchr
 141         jmp     prtstr
 142 fin:    ret
 143 
 144 ! Space printing
 145 
 146 prtsp2: call    prtspc          ! Print double space
 147 prtspc: mov     al,#0x20        ! Print single space (fall-thru!)
 148 
 149 ! Part of above routine, this one just prints ascii al
 150 
 151 prtchr: push    ax
 152         push    cx
 153         xor     bh,bh
 154         mov     cx,#0x01
 155         mov     ah,#0x0e
 156         int     0x10
 157         pop     cx
 158         pop     ax
 159         ret
 160 
 161 beep:   mov     al,#0x07
 162         jmp     prtchr
 163         
 164 no_sig_mess:    .ascii  "No setup signature found ..."
 165                 db      0x00
 166 
 167 good_sig1:
 168         jmp     good_sig
 169 
 170 ! We now have to find the rest of the setup code/data
 171 bad_sig:
 172         mov     ax,cs           ! aka #SETUPSEG
 173         sub     ax,#DELTA_INITSEG ! aka #INITSEG
 174         mov     ds,ax
 175         xor     bh,bh
 176         mov     bl,[497]        ! get setup sects from boot sector
 177         sub     bx,#4           ! LILO loads 4 sectors of setup
 178         shl     bx,#8           ! convert to words
 179         mov     cx,bx
 180         shr     bx,#3           ! convert to segment
 181         add     bx,#SYSSEG
 182         seg cs
 183         mov     start_sys_seg,bx
 184 
 185 ! Move rest of setup code/data to here
 186         mov     di,#2048        ! four sectors loaded by LILO
 187         sub     si,si
 188         mov     ax,cs           ! aka #SETUPSEG
 189         mov     es,ax
 190         mov     ax,#SYSSEG
 191         mov     ds,ax
 192         rep
 193         movsw
 194 
 195         mov     ax,cs           ! aka #SETUPSEG
 196         mov     ds,ax
 197         cmp     setup_sig1,#SIG1
 198         jne     no_sig
 199         cmp     setup_sig2,#SIG2
 200         jne     no_sig
 201         jmp     good_sig
 202 
 203 no_sig:
 204         lea     si,no_sig_mess
 205         call    prtstr
 206 no_sig_loop:
 207         jmp     no_sig_loop
 208 
 209 good_sig:
 210         mov     ax,cs           ! aka #SETUPSEG
 211         sub     ax,#DELTA_INITSEG ! aka #INITSEG
 212         mov     ds,ax
 213 
 214 ! check if an old loader tries to load a big-kernel
 215         seg cs
 216         test    byte ptr loadflags,#LOADED_HIGH ! have we a big kernel ?
 217         jz      loader_ok       ! NO, no danger even for old loaders
 218                                 ! YES, we have a big-kernel
 219         seg cs
 220         cmp     byte ptr type_of_loader,#0 ! have we one of the new loaders ?
 221         jnz     loader_ok       ! YES, ok
 222                                 ! NO, we have an old loader, must give up
 223         push    cs
 224         pop     ds
 225         lea     si,loader_panic_mess
 226         call    prtstr
 227         jmp     no_sig_loop
 228 loader_panic_mess: 
 229         .ascii  "Wrong loader, giving up..."
 230         db      0
 231 
 232 loader_ok:
 233 ! Get memory size (extended mem, kB)
 234 
 235         mov     ah,#0x88
 236         int     0x15
 237         mov     [2],ax
 238 
 239 ! Set the keyboard repeat rate to the max
 240 
 241         mov     ax,#0x0305
 242         xor     bx,bx           ! clear bx
 243         int     0x16
 244 
 245 ! Check for video adapter and its parameters and allow the
 246 ! user to browse video modes.
 247 
 248         call    video   ! NOTE: we need DS pointing to bootsector
 249 
 250 ! Get hd0 data
 251 
 252         xor     ax,ax           ! clear ax
 253         mov     ds,ax
 254         lds     si,[4*0x41]
 255         mov     ax,cs           ! aka #SETUPSEG
 256         sub     ax,#DELTA_INITSEG ! aka #INITSEG
 257         push    ax
 258         mov     es,ax
 259         mov     di,#0x0080
 260         mov     cx,#0x10
 261         push    cx
 262         cld
 263         rep
 264         movsb
 265 
 266 ! Get hd1 data
 267 
 268         xor     ax,ax           ! clear ax
 269         mov     ds,ax
 270         lds     si,[4*0x46]
 271         pop     cx
 272         pop     es
 273         mov     di,#0x0090
 274         rep
 275         movsb
 276 
 277 ! Check that there IS a hd1 :-)
 278 
 279         mov     ax,#0x01500
 280         mov     dl,#0x81
 281         int     0x13
 282         jc      no_disk1
 283         cmp     ah,#3
 284         je      is_disk1
 285 no_disk1:
 286         mov     ax,cs           ! aka #SETUPSEG
 287         sub     ax,#DELTA_INITSEG ! aka #INITSEG
 288         mov     es,ax
 289         mov     di,#0x0090
 290         mov     cx,#0x10
 291         xor     ax,ax           ! clear ax
 292         cld
 293         rep
 294         stosb
 295 is_disk1:
 296 
 297 ! Check for PS/2 pointing device
 298 
 299         mov     ax,cs           ! aka #SETUPSEG
 300         sub     ax,#DELTA_INITSEG ! aka #INITSEG
 301         mov     ds,ax
 302         mov     [0x1ff],#0      ! default is no pointing device
 303         int     0x11            ! int 0x11: equipment determination
 304         test    al,#0x04        ! check if pointing device installed
 305         jz      no_psmouse
 306         mov     [0x1ff],#0xaa   ! device present
 307 no_psmouse:
 308 
 309 #ifdef CONFIG_APM
 310 ! check for APM BIOS
 311                 ! NOTE: DS is pointing to the bootsector
 312                 !
 313         mov     [64],#0         ! version == 0 means no APM BIOS
 314 
 315         mov     ax,#0x05300     ! APM BIOS installation check
 316         xor     bx,bx
 317         int     0x15
 318         jc      done_apm_bios   ! error -> no APM BIOS
 319 
 320         cmp     bx,#0x0504d     ! check for "PM" signature
 321         jne     done_apm_bios   ! no signature -> no APM BIOS
 322 
 323         mov     [64],ax         ! record the APM BIOS version
 324         mov     [76],cx         !       and flags
 325         and     cx,#0x02        ! Is 32 bit supported?
 326         je      done_apm_bios   !       no ...
 327 
 328         mov     ax,#0x05304     ! Disconnect first just in case
 329         xor     bx,bx
 330         int     0x15            ! ignore return code
 331 
 332         mov     ax,#0x05303     ! 32 bit connect
 333         xor     bx,bx
 334         int     0x15
 335         jc      no_32_apm_bios  ! error
 336 
 337         mov     [66],ax         ! BIOS code segment
 338         mov     [68],ebx        ! BIOS entry point offset
 339         mov     [72],cx         ! BIOS 16 bit code segment
 340         mov     [74],dx         ! BIOS data segment
 341         mov     [78],si         ! BIOS code segment length
 342         mov     [80],di         ! BIOS data segment length
 343         jmp     done_apm_bios
 344 
 345 no_32_apm_bios:
 346         and     [76], #0xfffd   ! remove 32 bit support bit
 347 
 348 done_apm_bios:
 349 #endif
 350 
 351 ! Now we want to move to protected mode ...
 352 
 353         seg cs
 354         cmp     realmode_swtch,#0
 355         jz      rmodeswtch_normal
 356         seg cs
 357         callf   far * realmode_swtch
 358         jmp     rmodeswtch_end
 359 rmodeswtch_normal:
 360         push    cs
 361         call    default_switch
 362 rmodeswtch_end:
 363 
 364 ! we get the code32 start address and modify the below 'jmpi'
 365 ! (loader may have changed it)
 366         seg cs
 367         mov     eax,code32_start
 368         seg cs
 369         mov     code32,eax
 370 
 371 ! Now we move the system to its rightful place
 372 ! ...but we check, if we have a big-kernel.
 373 ! in this case we *must* not move it ...
 374         seg cs
 375         test    byte ptr loadflags,#LOADED_HIGH
 376         jz      do_move0        ! we have a normal low loaded zImage
 377                                 ! we have a high loaded big kernel
 378         jmp     end_move        ! ... and we skip moving
 379 
 380 do_move0:
 381         mov     ax,#0x100       ! start of destination segment
 382         mov     bp,cs           ! aka #SETUPSEG
 383         sub     bp,#DELTA_INITSEG ! aka #INITSEG
 384         seg cs
 385         mov     bx,start_sys_seg        ! start of source segment
 386         cld                     ! 'direction'=0, movs moves forward
 387 do_move:
 388         mov     es,ax           ! destination segment
 389         inc     ah              ! instead of add ax,#0x100
 390         mov     ds,bx           ! source segment
 391         add     bx,#0x100
 392         sub     di,di
 393         sub     si,si
 394         mov     cx,#0x800
 395         rep
 396         movsw
 397         cmp     bx,bp           ! we assume start_sys_seg > 0x200,
 398                                 ! so we will perhaps read one page more then
 399                                 ! needed, but never overwrite INITSEG because
 400                                 ! destination is minimum one page below source
 401         jb      do_move
 402 
 403 ! then we load the segment descriptors
 404 
 405 end_move:
 406         mov     ax,cs ! aka #SETUPSEG   ! right, forgot this at first. didn't work :-)
 407         mov     ds,ax
 408 
 409 ! If we have our code not at 0x90000, we need to move it there now.
 410 ! We also then need to move the params behind it (commandline)
 411 ! Because we would overwrite the code on the current IP, we move
 412 ! it in two steps, jumping high after the first one.
 413         mov     ax,cs
 414         cmp     ax,#SETUPSEG
 415         je      end_move_self
 416         cli     ! make sure we really have interrupts disabled !
 417                 ! because after this the stack should not be used
 418         sub     ax,#DELTA_INITSEG ! aka #INITSEG
 419         mov     dx,ss
 420         cmp     dx,ax
 421         jb      move_self_1
 422         add     dx,#INITSEG
 423         sub     dx,ax           ! this will be SS after the move
 424 move_self_1:
 425         mov     ds,ax
 426         mov     ax,#INITSEG     ! real INITSEG
 427         mov     es,ax
 428         seg cs
 429         mov     cx,setup_move_size
 430         std             ! we have to move up, so we use direction down
 431                         ! because the areas may overlap
 432         mov     di,cx
 433         dec     di
 434         mov     si,di
 435         sub     cx,#move_self_here+0x200
 436         rep
 437         movsb
 438         jmpi    move_self_here,SETUPSEG ! jump to our final place
 439 move_self_here:
 440         mov     cx,#move_self_here+0x200
 441         rep
 442         movsb
 443         mov     ax,#SETUPSEG
 444         mov     ds,ax
 445         mov     ss,dx
 446                         ! now we are at the right place
 447 end_move_self:
 448 
 449         lidt    idt_48          ! load idt with 0,0
 450         lgdt    gdt_48          ! load gdt with whatever appropriate
 451 
 452 ! that was painless, now we enable A20
 453 
 454         call    empty_8042
 455         mov     al,#0xD1                ! command write
 456         out     #0x64,al
 457         call    empty_8042
 458         mov     al,#0xDF                ! A20 on
 459         out     #0x60,al
 460         call    empty_8042
 461 
 462 ! make sure any possible coprocessor is properly reset..
 463 
 464         xor     ax,ax
 465         out     #0xf0,al
 466         call    delay
 467         out     #0xf1,al
 468         call    delay
 469 
 470 ! well, that went ok, I hope. Now we have to reprogram the interrupts :-(
 471 ! we put them right after the intel-reserved hardware interrupts, at
 472 ! int 0x20-0x2F. There they won't mess up anything. Sadly IBM really
 473 ! messed this up with the original PC, and they haven't been able to
 474 ! rectify it afterwards. Thus the bios puts interrupts at 0x08-0x0f,
 475 ! which is used for the internal hardware interrupts as well. We just
 476 ! have to reprogram the 8259's, and it isn't fun.
 477 
 478         mov     al,#0x11                ! initialization sequence
 479         out     #0x20,al                ! send it to 8259A-1
 480         call    delay
 481         out     #0xA0,al                ! and to 8259A-2
 482         call    delay
 483         mov     al,#0x20                ! start of hardware int's (0x20)
 484         out     #0x21,al
 485         call    delay
 486         mov     al,#0x28                ! start of hardware int's 2 (0x28)
 487         out     #0xA1,al
 488         call    delay
 489         mov     al,#0x04                ! 8259-1 is master
 490         out     #0x21,al
 491         call    delay
 492         mov     al,#0x02                ! 8259-2 is slave
 493         out     #0xA1,al
 494         call    delay
 495         mov     al,#0x01                ! 8086 mode for both
 496         out     #0x21,al
 497         call    delay
 498         out     #0xA1,al
 499         call    delay
 500         mov     al,#0xFF                ! mask off all interrupts for now
 501         out     #0xA1,al
 502         call    delay
 503         mov     al,#0xFB                ! mask all irq's but irq2 which
 504         out     #0x21,al                ! is cascaded
 505 
 506 ! Well, that certainly wasn't fun :-(. Hopefully it works, and we don't
 507 ! need no steenking BIOS anyway (except for the initial loading :-).
 508 ! The BIOS-routine wants lots of unnecessary data, and it's less
 509 ! "interesting" anyway. This is how REAL programmers do it.
 510 !
 511 ! Well, now's the time to actually move into protected mode. To make
 512 ! things as simple as possible, we do no register set-up or anything,
 513 ! we let the gnu-compiled 32-bit programs do that. We just jump to
 514 ! absolute address 0x1000 (or the loader supplied one),
 515 ! in 32-bit protected mode.
 516 !
 517 ! Note that the short jump isn't strictly needed, although there are
 518 ! reasons why it might be a good idea. It won't hurt in any case.
 519 !
 520         mov     ax,#1           ! protected mode (PE) bit
 521         lmsw    ax              ! This is it!
 522         jmp     flush_instr
 523 flush_instr:
 524         xor     bx,bx           ! Flag to indicate a boot
 525 
 526 ! NOTE: For high loaded big kernels we need a
 527 !       jmpi    0x100000,KERNEL_CS
 528 !
 529 !       but we yet haven't reloaded the CS register, so the default size 
 530 !       of the target offset still is 16 bit.
 531 !       However, using an operant prefix (0x66), the CPU will properly
 532 !       take our 48 bit far pointer. (INTeL 80386 Programmer's Reference
 533 !       Manual, Mixing 16-bit and 32-bit code, page 16-6)
 534         db      0x66,0xea       ! prefix + jmpi-opcode
 535 code32: dd      0x1000          ! will be set to 0x100000 for big kernels
 536         dw      KERNEL_CS
 537 
 538 
 539 kernel_version: .ascii  UTS_RELEASE
 540                 .ascii  " ("
 541                 .ascii  LINUX_COMPILE_BY
 542                 .ascii  "@"
 543                 .ascii  LINUX_COMPILE_HOST
 544                 .ascii  ") "
 545                 .ascii  UTS_VERSION
 546                 db      0
 547 
 548 ! This is the default real mode switch routine.
 549 ! to be called just before protected mode transition
 550 
 551 default_switch:
 552         cli                     ! no interrupts allowed !
 553         mov     al,#0x80        ! disable NMI for the bootup sequence
 554         out     #0x70,al
 555         retf
 556 
 557 ! This routine only gets called, if we get loaded by the simple
 558 ! bootsect loader _and_ have a bzImage to load.
 559 ! Because there is no place left in the 512 bytes of the boot sector,
 560 ! we must emigrate to code space here.
 561 !
 562 bootsect_helper:
 563         seg cs
 564         cmp     word ptr bootsect_es,#0
 565         jnz     bootsect_second
 566         seg cs
 567         mov     byte ptr type_of_loader,#0x20
 568         mov     ax,es
 569         shr     ax,#4
 570         seg     cs
 571         mov     byte ptr bootsect_src_base+2,ah
 572         mov     ax,es
 573         seg cs
 574         mov     bootsect_es,ax
 575         sub     ax,#SYSSEG
 576         retf                    ! nothing else to do for now
 577 bootsect_second:
 578         push    cx
 579         push    si
 580         push    bx
 581         test    bx,bx   ! 64K full ?
 582         jne     bootsect_ex
 583         mov     cx,#0x8000      ! full 64K move, INT15 moves words
 584         push    cs
 585         pop     es
 586         mov     si,#bootsect_gdt
 587         mov     ax,#0x8700
 588         int     0x15
 589         jc      bootsect_panic  ! this, if INT15 fails
 590         seg cs
 591         mov     es,bootsect_es  ! we reset es to always point to 0x10000
 592         seg cs
 593         inc     byte ptr bootsect_dst_base+2
 594 bootsect_ex:
 595         seg cs
 596         mov     ah, byte ptr bootsect_dst_base+2
 597         shl     ah,4    ! we now have the number of moved frames in ax
 598         xor     al,al
 599         pop     bx
 600         pop     si
 601         pop     cx
 602         retf
 603 
 604 bootsect_gdt:
 605         .word   0,0,0,0
 606         .word   0,0,0,0
 607 bootsect_src:
 608         .word   0xffff
 609 bootsect_src_base:
 610         .byte   0,0,1                   ! base = 0x010000
 611         .byte   0x93                    ! typbyte
 612         .word   0                       ! limit16,base24 =0
 613 bootsect_dst:
 614         .word   0xffff
 615 bootsect_dst_base:
 616         .byte   0,0,0x10                ! base = 0x100000
 617         .byte   0x93                    ! typbyte
 618         .word   0                       ! limit16,base24 =0
 619         .word   0,0,0,0                 ! BIOS CS
 620         .word   0,0,0,0                 ! BIOS DS
 621 bootsect_es:
 622         .word   0
 623 
 624 bootsect_panic:
 625         push    cs
 626         pop     ds
 627         cld
 628         lea     si,bootsect_panic_mess
 629         call    prtstr
 630 bootsect_panic_loop:
 631         jmp     bootsect_panic_loop
 632 bootsect_panic_mess:
 633         .ascii  "INT15 refuses to access high mem, giving up..."
 634         db      0
 635 
 636 ! This routine checks that the keyboard command queue is empty
 637 ! (after emptying the output buffers)
 638 !
 639 ! No timeout is used - if this hangs there is something wrong with
 640 ! the machine, and we probably couldn't proceed anyway.
 641 empty_8042:
 642         call    delay
 643         in      al,#0x64        ! 8042 status port
 644         test    al,#1           ! output buffer?
 645         jz      no_output
 646         call    delay
 647         in      al,#0x60        ! read it
 648         jmp     empty_8042
 649 no_output:
 650         test    al,#2           ! is input buffer full?
 651         jnz     empty_8042      ! yes - loop
 652         ret
 653 
 654 !
 655 ! Read the cmos clock. Return the seconds in al
 656 !
 657 gettime:
 658         push    cx
 659         mov     ah,#0x02
 660         int     0x1a
 661         mov     al,dh                   ! dh contains the seconds
 662         and     al,#0x0f
 663         mov     ah,dh
 664         mov     cl,#0x04
 665         shr     ah,cl
 666         aad
 667         pop     cx
 668         ret
 669 
 670 !
 671 ! Delay is needed after doing I/O
 672 !
 673 delay:
 674         .word   0x00eb                  ! jmp $+2
 675         ret
 676 
 677 !
 678 ! Descriptor tables
 679 !
 680 
 681 gdt:
 682         .word   0,0,0,0         ! dummy
 683 
 684         .word   0,0,0,0         ! unused
 685 
 686         .word   0xFFFF          ! 4Gb - (0x100000*0x1000 = 4Gb)
 687         .word   0x0000          ! base address=0
 688         .word   0x9A00          ! code read/exec
 689         .word   0x00CF          ! granularity=4096, 386 (+5th nibble of limit)
 690 
 691         .word   0xFFFF          ! 4Gb - (0x100000*0x1000 = 4Gb)
 692         .word   0x0000          ! base address=0
 693         .word   0x9200          ! data read/write
 694         .word   0x00CF          ! granularity=4096, 386 (+5th nibble of limit)
 695 
 696 idt_48:
 697         .word   0                       ! idt limit=0
 698         .word   0,0                     ! idt base=0L
 699 
 700 gdt_48:
 701         .word   0x800           ! gdt limit=2048, 256 GDT entries
 702         .word   512+gdt,0x9     ! gdt base = 0X9xxxx
 703 
 704 !
 705 ! Include video setup & detection code
 706 !
 707 
 708 #include "video.S"
 709 
 710 !
 711 ! Setup signature -- must be last
 712 !
 713 
 714 setup_sig1:     .word   SIG1
 715 setup_sig2:     .word   SIG2
 716 
 717 !
 718 ! After this point, there is some free space which is used by the video mode
 719 ! handling code to store the temporary mode table (not used by the kernel).
 720 !
 721 
 722 modelist:
 723 
 724 .text
 725 endtext:
 726 .data
 727 enddata:
 728 .bss
 729 endbss:

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