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

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