OpenCores
URL https://opencores.org/ocsvn/or1k/or1k/trunk

Subversion Repositories or1k

[/] [or1k/] [trunk/] [uclinux/] [uClinux-2.0.x/] [arch/] [i386/] [boot/] [setup.S] - Blame information for rev 1765

Details | Compare with Previous | View Log

Line No. Rev Author Line
1 199 simons
!
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@canb.auug.org.au)
22
!
23
! High load stuff, initrd support and position independency
24
! by Hans Lermen & Werner Almesberger, February 1996
25
! , 
26
!
27
! Video handling moved to video.S by Martin Mares, March 1996
28
! 
29
 
30
! NOTE! These had better be the same as in bootsect.s!
31
#define __ASSEMBLY__
32
#include 
33
#include 
34
#include 
35
#include 
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
#ifndef STANDARD_MEMORY_BIOS_CALL
236
        push    ebx
237
 
238
        xor     ebx,ebx         ! preload new memory slot with 0k
239
        mov     [0x1e0], ebx
240
 
241
        mov     ax,#0xe801
242
        int     0x15
243
        jc      oldstylemem
244
 
245
        and     ebx, #0xffff    ! clear sign extend
246
        shl     ebx, 6          ! and go from 64k to 1k chunks
247
        mov     [0x1e0],ebx     ! store extended memory size
248
 
249
        and     eax, #0xffff    ! clear sign extend
250
        add     [0x1e0],eax     ! and add lower memory into total size.
251
 
252
        ! and fall into the old memory detection code to populate the
253
        ! compatability slot.
254
 
255
oldstylemem:
256
        pop     ebx
257
#endif
258
        mov     ah,#0x88
259
        int     0x15
260
        mov     [2],ax
261
 
262
! Set the keyboard repeat rate to the max
263
 
264
        mov     ax,#0x0305
265
        xor     bx,bx           ! clear bx
266
        int     0x16
267
 
268
! Check for video adapter and its parameters and allow the
269
! user to browse video modes.
270
 
271
        call    video   ! NOTE: we need DS pointing to bootsector
272
 
273
! Get hd0 data
274
 
275
        xor     ax,ax           ! clear ax
276
        mov     ds,ax
277
        lds     si,[4*0x41]
278
        mov     ax,cs           ! aka #SETUPSEG
279
        sub     ax,#DELTA_INITSEG ! aka #INITSEG
280
        push    ax
281
        mov     es,ax
282
        mov     di,#0x0080
283
        mov     cx,#0x10
284
        push    cx
285
        cld
286
        rep
287
        movsb
288
 
289
! Get hd1 data
290
 
291
        xor     ax,ax           ! clear ax
292
        mov     ds,ax
293
        lds     si,[4*0x46]
294
        pop     cx
295
        pop     es
296
        mov     di,#0x0090
297
        rep
298
        movsb
299
 
300
! Check that there IS a hd1 :-)
301
 
302
        mov     ax,#0x01500
303
        mov     dl,#0x81
304
        int     0x13
305
        jc      no_disk1
306
        cmp     ah,#3
307
        je      is_disk1
308
no_disk1:
309
        mov     ax,cs           ! aka #SETUPSEG
310
        sub     ax,#DELTA_INITSEG ! aka #INITSEG
311
        mov     es,ax
312
        mov     di,#0x0090
313
        mov     cx,#0x10
314
        xor     ax,ax           ! clear ax
315
        cld
316
        rep
317
        stosb
318
is_disk1:
319
 
320
! Check for PS/2 pointing device
321
 
322
        mov     ax,cs           ! aka #SETUPSEG
323
        sub     ax,#DELTA_INITSEG ! aka #INITSEG
324
        mov     ds,ax
325
        mov     [0x1ff],#0      ! default is no pointing device
326
        int     0x11            ! int 0x11: equipment determination
327
        test    al,#0x04        ! check if pointing device installed
328
        jz      no_psmouse
329
        mov     [0x1ff],#0xaa   ! device present
330
no_psmouse:
331
 
332
#ifdef CONFIG_APM
333
! check for APM BIOS
334
                ! NOTE: DS is pointing to the boot sector
335
                !
336
        mov     [64],#0         ! version == 0 means no APM BIOS
337
 
338
        mov     ax,#0x05300     ! APM BIOS installation check
339
        xor     bx,bx
340
        int     0x15
341
        jc      done_apm_bios   ! error -> no APM BIOS
342
 
343
        cmp     bx,#0x0504d     ! check for "PM" signature
344
        jne     done_apm_bios   ! no signature -> no APM BIOS
345
 
346
        mov     [64],ax         ! record the APM BIOS version
347
        mov     [76],cx         !       and flags
348
        and     cx,#0x02        ! Is 32 bit supported?
349
        je      done_apm_bios   !       no ...
350
 
351
        mov     ax,#0x05304     ! Disconnect first just in case
352
        xor     bx,bx
353
        int     0x15            ! ignore return code
354
 
355
        mov     ax,#0x05303     ! 32 bit connect
356
        xor     bx,bx
357
        int     0x15
358
        jc      no_32_apm_bios  ! error
359
 
360
        mov     [66],ax         ! BIOS code segment
361
        mov     [68],ebx        ! BIOS entry point offset
362
        mov     [72],cx         ! BIOS 16 bit code segment
363
        mov     [74],dx         ! BIOS data segment
364
        mov     [78],si         ! BIOS code segment length
365
        mov     [80],di         ! BIOS data segment length
366
        jmp     done_apm_bios
367
 
368
no_32_apm_bios:
369
        and     [76], #0xfffd   ! remove 32 bit support bit
370
 
371
done_apm_bios:
372
#endif
373
 
374
! Now we want to move to protected mode ...
375
 
376
        seg cs
377
        cmp     realmode_swtch,#0
378
        jz      rmodeswtch_normal
379
        seg cs
380
        callf   far * realmode_swtch
381
        jmp     rmodeswtch_end
382
rmodeswtch_normal:
383
        push    cs
384
        call    default_switch
385
rmodeswtch_end:
386
 
387
! we get the code32 start address and modify the below 'jmpi'
388
! (loader may have changed it)
389
        seg cs
390
        mov     eax,code32_start
391
        seg cs
392
        mov     code32,eax
393
 
394
! Now we move the system to its rightful place
395
! ...but we check, if we have a big-kernel.
396
! in this case we *must* not move it ...
397
        seg cs
398
        test    byte ptr loadflags,#LOADED_HIGH
399
        jz      do_move0        ! we have a normal low loaded zImage
400
                                ! we have a high loaded big kernel
401
        jmp     end_move        ! ... and we skip moving
402
 
403
do_move0:
404
        mov     ax,#0x100       ! start of destination segment
405
        mov     bp,cs           ! aka #SETUPSEG
406
        sub     bp,#DELTA_INITSEG ! aka #INITSEG
407
        seg cs
408
        mov     bx,start_sys_seg        ! start of source segment
409
        cld                     ! 'direction'=0, movs moves forward
410
do_move:
411
        mov     es,ax           ! destination segment
412
        inc     ah              ! instead of add ax,#0x100
413
        mov     ds,bx           ! source segment
414
        add     bx,#0x100
415
        sub     di,di
416
        sub     si,si
417
        mov     cx,#0x800
418
        rep
419
        movsw
420
        cmp     bx,bp           ! we assume start_sys_seg > 0x200,
421
                                ! so we will perhaps read one page more then
422
                                ! needed, but never overwrite INITSEG because
423
                                ! destination is minimum one page below source
424
        jb      do_move
425
 
426
! then we load the segment descriptors
427
 
428
end_move:
429
        mov     ax,cs ! aka #SETUPSEG   ! right, forgot this at first. didn't work :-)
430
        mov     ds,ax
431
 
432
! If we have our code not at 0x90000, we need to move it there now.
433
! We also then need to move the params behind it (commandline)
434
! Because we would overwrite the code on the current IP, we move
435
! it in two steps, jumping high after the first one.
436
        mov     ax,cs
437
        cmp     ax,#SETUPSEG
438
        je      end_move_self
439
        cli     ! make sure we really have interrupts disabled !
440
                ! because after this the stack should not be used
441
        sub     ax,#DELTA_INITSEG ! aka #INITSEG
442
        mov     dx,ss
443
        cmp     dx,ax
444
        jb      move_self_1
445
        add     dx,#INITSEG
446
        sub     dx,ax           ! this will be SS after the move
447
move_self_1:
448
        mov     ds,ax
449
        mov     ax,#INITSEG     ! real INITSEG
450
        mov     es,ax
451
        seg cs
452
        mov     cx,setup_move_size
453
        std             ! we have to move up, so we use direction down
454
                        ! because the areas may overlap
455
        mov     di,cx
456
        dec     di
457
        mov     si,di
458
        sub     cx,#move_self_here+0x200
459
        rep
460
        movsb
461
        jmpi    move_self_here,SETUPSEG ! jump to our final place
462
move_self_here:
463
        mov     cx,#move_self_here+0x200
464
        rep
465
        movsb
466
        mov     ax,#SETUPSEG
467
        mov     ds,ax
468
        mov     ss,dx
469
                        ! now we are at the right place
470
end_move_self:
471
 
472
        lidt    idt_48          ! load idt with 0,0
473
        lgdt    gdt_48          ! load gdt with whatever appropriate
474
 
475
! that was painless, now we enable A20
476
 
477
        call    empty_8042
478
        mov     al,#0xD1                ! command write
479
        out     #0x64,al
480
        call    empty_8042
481
        mov     al,#0xDF                ! A20 on
482
        out     #0x60,al
483
        call    empty_8042
484
 
485
! wait until a20 really *is* enabled; it can take a fair amount of
486
! time on certain systems; Toshiba Tecras are known to have this
487
! problem.  The memory location used here is the int 0x1f vector,
488
! which should be safe to use; any *unused* memory location < 0xfff0
489
! should work here.
490
 
491
#define TEST_ADDR 0x7c
492
 
493
        push    ds
494
        xor     ax,ax                   ! segment 0x0000
495
        mov     ds,ax
496
        dec     ax                      ! segment 0xffff (HMA)
497
        mov     gs,ax
498
        mov     bx,[TEST_ADDR]          ! we want to restore the value later
499
a20_wait:
500
        inc     ax
501
        mov     [TEST_ADDR],ax
502
        seg     gs
503
        cmp     ax,[TEST_ADDR+0x10]
504
        je      a20_wait                ! loop until no longer aliased
505
        mov     [TEST_ADDR],bx          ! restore original value
506
        pop     ds
507
 
508
! make sure any possible coprocessor is properly reset..
509
 
510
        xor     ax,ax
511
        out     #0xf0,al
512
        call    delay
513
        out     #0xf1,al
514
        call    delay
515
 
516
! well, that went ok, I hope. Now we have to reprogram the interrupts :-(
517
! we put them right after the intel-reserved hardware interrupts, at
518
! int 0x20-0x2F. There they won't mess up anything. Sadly IBM really
519
! messed this up with the original PC, and they haven't been able to
520
! rectify it afterwards. Thus the bios puts interrupts at 0x08-0x0f,
521
! which is used for the internal hardware interrupts as well. We just
522
! have to reprogram the 8259's, and it isn't fun.
523
 
524
        mov     al,#0x11                ! initialization sequence
525
        out     #0x20,al                ! send it to 8259A-1
526
        call    delay
527
        out     #0xA0,al                ! and to 8259A-2
528
        call    delay
529
        mov     al,#0x20                ! start of hardware int's (0x20)
530
        out     #0x21,al
531
        call    delay
532
        mov     al,#0x28                ! start of hardware int's 2 (0x28)
533
        out     #0xA1,al
534
        call    delay
535
        mov     al,#0x04                ! 8259-1 is master
536
        out     #0x21,al
537
        call    delay
538
        mov     al,#0x02                ! 8259-2 is slave
539
        out     #0xA1,al
540
        call    delay
541
        mov     al,#0x01                ! 8086 mode for both
542
        out     #0x21,al
543
        call    delay
544
        out     #0xA1,al
545
        call    delay
546
        mov     al,#0xFF                ! mask off all interrupts for now
547
        out     #0xA1,al
548
        call    delay
549
        mov     al,#0xFB                ! mask all irq's but irq2 which
550
        out     #0x21,al                ! is cascaded
551
 
552
! Well, that certainly wasn't fun :-(. Hopefully it works, and we don't
553
! need no steenking BIOS anyway (except for the initial loading :-).
554
! The BIOS-routine wants lots of unnecessary data, and it's less
555
! "interesting" anyway. This is how REAL programmers do it.
556
!
557
! Well, now's the time to actually move into protected mode. To make
558
! things as simple as possible, we do no register set-up or anything,
559
! we let the gnu-compiled 32-bit programs do that. We just jump to
560
! absolute address 0x1000 (or the loader supplied one),
561
! in 32-bit protected mode.
562
!
563
! Note that the short jump isn't strictly needed, although there are
564
! reasons why it might be a good idea. It won't hurt in any case.
565
!
566
        mov     ax,#1           ! protected mode (PE) bit
567
        lmsw    ax              ! This is it!
568
        jmp     flush_instr
569
flush_instr:
570
        xor     bx,bx           ! Flag to indicate a boot
571
 
572
! NOTE: For high loaded big kernels we need a
573
!       jmpi    0x100000,KERNEL_CS
574
!
575
!       but we yet haven't reloaded the CS register, so the default size
576
!       of the target offset still is 16 bit.
577
!       However, using an operant prefix (0x66), the CPU will properly
578
!       take our 48 bit far pointer. (INTeL 80386 Programmer's Reference
579
!       Manual, Mixing 16-bit and 32-bit code, page 16-6)
580
        db      0x66,0xea       ! prefix + jmpi-opcode
581
code32: dd      0x1000          ! will be set to 0x100000 for big kernels
582
        dw      KERNEL_CS
583
 
584
 
585
kernel_version: .ascii  UTS_RELEASE
586
                .ascii  " ("
587
                .ascii  LINUX_COMPILE_BY
588
                .ascii  "@"
589
                .ascii  LINUX_COMPILE_HOST
590
                .ascii  ") "
591
                .ascii  UTS_VERSION
592
                db      0
593
 
594
! This is the default real mode switch routine.
595
! to be called just before protected mode transition
596
 
597
default_switch:
598
        cli                     ! no interrupts allowed !
599
        mov     al,#0x80        ! disable NMI for the bootup sequence
600
        out     #0x70,al
601
        retf
602
 
603
! This routine only gets called, if we get loaded by the simple
604
! bootsect loader _and_ have a bzImage to load.
605
! Because there is no place left in the 512 bytes of the boot sector,
606
! we must emigrate to code space here.
607
!
608
bootsect_helper:
609
        seg cs
610
        cmp     word ptr bootsect_es,#0
611
        jnz     bootsect_second
612
        seg cs
613
        mov     byte ptr type_of_loader,#0x20
614
        mov     ax,es
615
        shr     ax,#4
616
        seg     cs
617
        mov     byte ptr bootsect_src_base+2,ah
618
        mov     ax,es
619
        seg cs
620
        mov     bootsect_es,ax
621
        sub     ax,#SYSSEG
622
        retf                    ! nothing else to do for now
623
bootsect_second:
624
        push    cx
625
        push    si
626
        push    bx
627
        test    bx,bx   ! 64K full ?
628
        jne     bootsect_ex
629
        mov     cx,#0x8000      ! full 64K move, INT15 moves words
630
        push    cs
631
        pop     es
632
        mov     si,#bootsect_gdt
633
        mov     ax,#0x8700
634
        int     0x15
635
        jc      bootsect_panic  ! this, if INT15 fails
636
        seg cs
637
        mov     es,bootsect_es  ! we reset es to always point to 0x10000
638
        seg cs
639
        inc     byte ptr bootsect_dst_base+2
640
bootsect_ex:
641
        seg cs
642
        mov     ah, byte ptr bootsect_dst_base+2
643
        shl     ah,4    ! we now have the number of moved frames in ax
644
        xor     al,al
645
        pop     bx
646
        pop     si
647
        pop     cx
648
        retf
649
 
650
bootsect_gdt:
651
        .word   0,0,0,0
652
        .word   0,0,0,0
653
bootsect_src:
654
        .word   0xffff
655
bootsect_src_base:
656
        .byte   0,0,1                   ! base = 0x010000
657
        .byte   0x93                    ! typbyte
658
        .word   0                        ! limit16,base24 =0
659
bootsect_dst:
660
        .word   0xffff
661
bootsect_dst_base:
662
        .byte   0,0,0x10                ! base = 0x100000
663
        .byte   0x93                    ! typbyte
664
        .word   0                        ! limit16,base24 =0
665
        .word   0,0,0,0                 ! BIOS CS
666
        .word   0,0,0,0                 ! BIOS DS
667
bootsect_es:
668
        .word   0
669
 
670
bootsect_panic:
671
        push    cs
672
        pop     ds
673
        cld
674
        lea     si,bootsect_panic_mess
675
        call    prtstr
676
bootsect_panic_loop:
677
        jmp     bootsect_panic_loop
678
bootsect_panic_mess:
679
        .ascii  "INT15 refuses to access high mem, giving up..."
680
        db      0
681
 
682
! This routine checks that the keyboard command queue is empty
683
! (after emptying the output buffers)
684
!
685
! No timeout is used - if this hangs there is something wrong with
686
! the machine, and we probably couldn't proceed anyway.
687
empty_8042:
688
        call    delay
689
        in      al,#0x64        ! 8042 status port
690
        test    al,#1           ! output buffer?
691
        jz      no_output
692
        call    delay
693
        in      al,#0x60        ! read it
694
        jmp     empty_8042
695
no_output:
696
        test    al,#2           ! is input buffer full?
697
        jnz     empty_8042      ! yes - loop
698
        ret
699
 
700
!
701
! Read the cmos clock. Return the seconds in al
702
!
703
gettime:
704
        push    cx
705
        mov     ah,#0x02
706
        int     0x1a
707
        mov     al,dh                   ! dh contains the seconds
708
        and     al,#0x0f
709
        mov     ah,dh
710
        mov     cl,#0x04
711
        shr     ah,cl
712
        aad
713
        pop     cx
714
        ret
715
 
716
!
717
! Delay is needed after doing I/O
718
!
719
delay:
720
        .word   0x00eb                  ! jmp $+2
721
        ret
722
 
723
!
724
! Descriptor tables
725
!
726
 
727
gdt:
728
        .word   0,0,0,0         ! dummy
729
 
730
        .word   0,0,0,0         ! unused
731
 
732
        .word   0xFFFF          ! 4Gb - (0x100000*0x1000 = 4Gb)
733
        .word   0x0000          ! base address=0
734
        .word   0x9A00          ! code read/exec
735
        .word   0x00CF          ! granularity=4096, 386 (+5th nibble of limit)
736
 
737
        .word   0xFFFF          ! 4Gb - (0x100000*0x1000 = 4Gb)
738
        .word   0x0000          ! base address=0
739
        .word   0x9200          ! data read/write
740
        .word   0x00CF          ! granularity=4096, 386 (+5th nibble of limit)
741
 
742
idt_48:
743
        .word   0                        ! idt limit=0
744
        .word   0,0                     ! idt base=0L
745
 
746
gdt_48:
747
        .word   0x800           ! gdt limit=2048, 256 GDT entries
748
        .word   512+gdt,0x9     ! gdt base = 0X9xxxx
749
 
750
!
751
! Include video setup & detection code
752
!
753
 
754
#include "video.S"
755
 
756
!
757
! Setup signature -- must be last
758
!
759
 
760
setup_sig1:     .word   SIG1
761
setup_sig2:     .word   SIG2
762
 
763
!
764
! After this point, there is some free space which is used by the video mode
765
! handling code to store the temporary mode table (not used by the kernel).
766
!
767
 
768
modelist:
769
 
770
.text
771
endtext:
772
.data
773
enddata:
774
.bss
775
endbss:

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.