1 ! Boothead.s
- BIOS support for boot.c Author
: Kees J. Bot
4 ! This file contains the startup
and low level support for the secondary
5 ! boot program. It contains functions for disk
, tty
and keyboard I
/O
,
6 ! copying memory to arbitrary locations
, etc.
8 ! The primary bootstrap code supplies the following parameters in registers
:
10 ! es
:si
= Partition table entry if hard disk.
14 o32
= 0x66 ! This assembler doesn
't know 386 extensions
15 BOOTOFF = 0x7C00 ! 0x0000:BOOTOFF load a bootstrap here
16 LOADSEG = 0x1000 ! Where this code is loaded.
17 BUFFER = 0x0600 ! First free memory
18 PENTRYSIZE = 16 ! Partition table entry size.
19 a_flags = 2 ! From a.out.h, struct exec
24 A_SEP = 0x20 ! Separate I&D flag
25 K_I386 = 0x0001 ! Call Minix in 386 mode
26 K_RET = 0x0020 ! Returns to the monitor on reboot
27 K_INT86 = 0x0040 ! Requires generic INT support
28 K_MEML = 0x0080 ! Pass a list of free memory
30 DS_SELECTOR = 3*8 ! Kernel data selector
31 ES_SELECTOR = 4*8 ! Flat 4 Gb
32 SS_SELECTOR = 5*8 ! Monitor stack
33 CS_SELECTOR = 6*8 ! Kernel code
34 MCS_SELECTOR= 7*8 ! Monitor code
36 ESC = 0x1B ! Escape character
38 ! Imported variables and functions:
39 .extern _caddr, _daddr, _runsize, _edata, _end ! Runtime environment
40 .extern _device ! BIOS device number
41 .extern _rem_part ! To pass partition info
42 .extern _k_flags ! Special kernel flags
43 .extern _mem ! Free memory list
44 .extern _cdbooted ! Whether we booted from CD
45 .extern _cddevice ! Whether we booted from CD
49 ! We assume boot is always linked with a short (32 byte) a.out header and has
50 ! 16 bytes of its own prefix, so 48 bytes to skip. bootblock jumps into us
51 ! at offset 0x30, cd boot code at 0x40
54 ! (skip short a.out header plus 16 byte preefix)
58 ! entry point when booting from CD
59 jmpf cdboot, LOADSEG+3
68 mov ds, ax ! ds = header
71 testb al, #A_SEP ! Separate I&D?
74 xchg ax, a_text ! No text
75 add a_data, ax ! Treat all text as data
77 mov ax, a_total ! Total nontext memory usage
78 and ax, #0xFFFE ! Round down to even
79 mov a_total, ax ! total - text = data + bss + heap + stack
80 cli ! Ignore interrupts while stack in limbo
81 mov sp, ax ! Set sp at the top of all that
83 mov ax, a_text ! Determine offset of ds above cs
88 mov ds, ax ! ds = cs + text / 16
91 push es ! Save es, we need it for the partition table
93 cld ! C compiler wants UP
97 mov di, #_edata ! Start of bss is at end of data
98 mov cx, #_end ! End of bss (begin of heap)
99 sub cx, di ! Number of bss bytes
100 shr cx, #1 ! Number of words
104 ! Copy primary boot parameters to variables. (Can do this now that bss is
105 ! cleared and may be written into).
107 mov _device, dx ! Boot device (probably 0x00 or 0x80)
108 mov _rem_part+0, si ! Remote partition table offset
109 pop _rem_part+2 ! and segment (saved es)
110 mov _cdbooted, bx ! Booted from CD? (bx set above)
112 ! Remember the current video mode for restoration on exit.
113 movb ah, #0x0F ! Get current video mode
115 andb al, #0x7F ! Mask off bit 7 (no blanking)
116 movb old_vid_mode, al
117 movb cur_vid_mode, al
119 ! Give C code access to the code segment, data segment and the size of this
133 mov ds, ax ! Back to the header once more
135 mov dx, a_total+2 ! dx:ax = data + bss + heap + stack
137 adc dx, a_text+2 ! dx:ax = text + data + bss + heap + stack
140 mov _runsize+2, dx ! 32 bit size of this process
142 ! Determine available memory as a list of (base,size) pairs as follows:
143 ! mem[0] = low memory, mem[1] = memory between 1M and 16M, mem[2] = memory
144 ! above 16M. Last two coalesced into mem[1] if adjacent.
145 mov di, #_mem ! di = memory list
146 int 0x12 ! Returns low memory size (in K) in ax
148 mov 4(di), ax ! mem[0].size = low memory size in bytes
151 cmp ax, #286 ! Only 286s and above have extended memory
153 cmp ax, #486 ! Assume 486s were the first to have >64M
154 jb small_ext ! (It helps to be paranoid when using the BIOS)
156 mov ax, #0xE801 ! Code for get memory size for >64M
157 int 0x15 ! ax = mem at 1M per 1K, bx = mem at 16M per 64K
160 movb ah, #0x88 ! Code for get extended memory size
161 clc ! Carry will stay clear if call exists
162 int 0x15 ! Returns size (in K) in ax for AT's
164 test ax
, ax
! An AT with no extended memory?
166 xor bx
, bx
! bx
= mem above
16M per
64K
= 0
168 mov cx
, ax
! cx
= copy of ext mem at
1M
169 mov
10(di
), #0x0010 ! mem[1].base = 0x00100000 (1M)
171 mov
12(di
), ax
! mem
[1].size = "ext mem at 1M" * 1024
174 jz no_ext
! No more ext mem above
16M?
175 cmp cx
, #15*1024 ! Chunks adjacent? (precisely 15M at 1M?)
177 mov
18(di
), #0x0100 ! mem[2].base = 0x01000000 (16M)
178 mov
22(di
), bx
! mem
[2].size = "ext mem at 16M" * 64K
181 add 14(di
), bx
! Add ext mem above
16M to mem below
16M
185 ! Time to switch to
a higher level language
(not much higher
)
188 ! void
..exit(int status)
189 ! Exit the monitor by rebooting the system.
190 .define _exit, __exit, ___exit ! Make various compilers happy
195 cmp 2(bx
), #0 ! Good exit status?
197 quit
: mov ax
, #any_key
200 xorb ah
, ah
! Read character from keyboard
202 reboot
: call dev_reset
204 int
0x19 ! Reboot the system
207 .ascii "\nHit any key to reboot\n\0"
210 ! u32_t mon2abs
(void
*ptr
)
211 ! Address in monitor data to absolute address.
216 mov dx
, ds
! Monitor data segment
219 ! u32_t vec2abs
(vector
*vec
)
220 ! 8086 interrupt vector to absolute address.
226 mov dx
, 2(bx
) ! dx
:ax vector
227 !jmp seg2abs
! Translate
229 seg2abs
: ! Translate dx
:ax to the
32 bit address dx-ax
234 shrb ch
, cl
! ch-dx
= dx
<< 4
236 adcb ch
, #0 ! ch-ax = ch-dx + ax
238 xorb dh
, dh
! dx-ax
= ch-ax
242 abs2seg
: ! Translate the
32 bit address dx-ax to dx
:ax
245 mov dx
, ax
! ch-dx
= dx-ax
246 and ax
, #0x000F ! Offset in ax
250 orb dh
, ch
! dx
= ch-dx
>> 4
254 ! void raw_copy
(u32_t dstaddr
, u32_t srcaddr
, u32_t count
)
255 ! Copy count bytes from srcaddr to dstaddr. Don
't do overlaps.
256 ! Also handles copying words to or from extended memory.
262 push di ! Save C variable registers
267 jcxz copydone ! Count is zero, end copy
270 bigcopy:mov cx, #0xFFF0 ! Don't copy more than about
64K at once
272 push cx
! Save copying count
275 cmp dx
, #0x0010 ! Copy to extended memory?
277 cmp 10(bp
), #0x0010 ! Copy from extended memory?
281 mov es
, dx
! es
:di
= dstaddr
286 mov ds
, dx
! ds
:si
= srcaddr
287 shr cx
, #1 ! Words to move
289 movs
! Do the word copy
290 adc cx
, cx
! One more byte?
292 movsb
! Do the byte copy
293 mov ax
, ss
! Restore ds
and es from the remaining ss
299 movb x_dst_desc+
4, dl
! Set base of destination segment
303 movb x_src_desc+
4, dl
! Set base of source segment
304 mov si
, #x_gdt ! es:si = global descriptor table
305 shr cx
, #1 ! Words to move
306 movb ah
, #0x87 ! Code for extended memory move
309 pop cx
! Restore count
311 adc
6(bp
), #0 ! srcaddr += copycount
313 adc
10(bp
), #0 ! dstaddr += copycount
315 sbb
14(bp
), #0 ! count -= copycount
316 jmp copy
! and repeat
319 pop si
! Restore C variable registers
323 ! u16_t get_word
(u32_t addr
);
324 ! void put_word
(u32_t addr
, u16_t word
);
325 ! Read
or write
a 16 bits word at an arbitrary location.
326 .define _get_word, _put_word
330 mov ax
, (bx
) ! Word to get from addr
334 push
6(bx
) ! Word to store at addr
336 pop
(bx
) ! Store the word
343 mov ds
, dx
! ds
:bx
= addr
350 ! void relocate
(void
);
351 ! After the program has copied itself to
a safer place
, it needs to change
352 ! the segment registers. Caddr has already been set to the new location.
355 pop bx
! Return address
359 mov cx
, dx
! cx
= new code segment
360 mov ax
, cs
! Old code segment
361 sub ax
, cx
! ax
= -(new
- old
) = -Moving offset
364 mov ds
, dx
! ds
+= (new
- old
)
370 mov _daddr+
2, dx
! New data address
371 push cx
! New text segment
372 push bx
! Return offset of this function
375 ! void
*brk
(void
*addr
)
376 ! void
*sbrk
(size_t incr
)
377 ! Cannot fail implementations of brk
(2) and sbrk
(3), so we can use
378 ! malloc
(3). They reboot on stack collision instead of returning -1.
381 break
: .data2 _end ! A fake heap pointer
383 .define _brk, __brk, _sbrk, __sbrk
385 __brk
: ! __brk is for the standard C compiler
387 jmp sbrk
! break
= 0; return sbrk
(addr
);
390 mov ax
, break
! ax
= current break
391 sbrk
: push ax
! save it as future return value
392 mov bx
, sp
! Stack is now
: (retval
, retaddr
, incr
, ...)
393 add ax
, 4(bx
) ! ax
= break
+ increment
394 mov break
, ax
! Set new break
395 lea dx
, -1024(bx
) ! sp minus
a bit of breathing space
396 cmp dx
, ax
! Compare with the new break
397 jb heaperr
! Suffocating noises
398 lea dx
, -4096(bx
) ! A warning when heap+stack goes
< 4K
400 jae plenty
! No reason to complain
403 call _printf
! Warn about memory running low
405 movb memwarn
, #0 ! No more warnings
406 plenty
: pop ax
! Return old break
(0 for brk
)
408 heaperr
:mov ax
, #chmem
415 nomem
: .ascii "\nOut of%s\0"
416 memwarn
:.ascii "\nLow on"
417 chmem
: .ascii " memory, use chmem to increase the heap\n\0"
420 ! int dev_open
(void
);
421 ! Given the device
"_device" figure out if it exists
and what its number
422 ! of heads
and sectors may be. Return the BIOS error code on error
,
426 call dev_reset
! Optionally reset the disks
427 movb dev_state
, #0 ! State is "closed"
429 push di
! Save registers used by BIOS calls
430 movb dl
, _device
! The default device
433 cmpb dl
, #0x80 ! Floppy < 0x80, winchester >= 0x80
436 mov di
, #3 ! Three tries to init drive by reading sector 0
439 mov bx
, #BUFFER ! es:bx = scratch buffer
440 mov ax
, #0x0201 ! Read sector, #sectors = 1
441 mov cx
, #0x0001 ! Track 0, first sector
442 xorb dh
, dh
! Drive dl
, head
0
444 jnc finit0ok
! Sector
0 read ok?
445 cmpb ah
, #0x80 ! Disk timed out? (Floppy drive empty)
449 xorb ah
, ah
! Reset drive
452 jmp finit0
! Retry once more
, it may need to spin up
454 mov di
, #seclist ! List of per floppy type sectors/track
455 flast
: movb cl
, (di
) ! Sectors per track to test
456 cmpb cl
, #9 ! No need to do the last 720K/360K test
460 mov bx
, #BUFFER ! es:bx = scratch buffer
461 mov ax
, #0x0201 ! Read sector, #sectors = 1
462 xorb ch
, ch
! Track
0, last sector
463 xorb dh
, dh
! Drive dl
, head
0
465 jnc ftestok
! Sector cl read ok?
466 xorb ah
, ah
! Reset drive
469 inc di
! Try next sec
/track number
472 movb dh
, #2 ! Floppies have two sides
475 movb ah
, #0x08 ! Code for drive parameters
476 int
0x13 ! dl still contains drive
477 jc geoerr
! No such drive?
478 andb cl
, #0x3F ! cl = max sector number (1-origin)
479 incb dh
! dh
= 1 + max head number
(0-origin
)
482 movb cl
, #0x3F ! Think up geometry for CD's
485 movb sectors
, cl
! Sectors per track
486 movb al
, cl
! al
= sectors per track
487 mulb dh
! ax
= heads
* sectors
488 mov secspcyl
, ax
! Sectors per cylinder
= heads
* sectors
489 movb dev_state
, #1 ! Device state is "open"
490 xor ax
, ax
! Code for success
493 pop es
! Restore di
and es registers
496 xorb ah
, ah
! ax
= BIOS error code
500 .data1 18, 15, 9 ! 1.44M, 1.2M, and 360K/720K floppy sec/track
503 ! int dev_close
(void
);
504 ! Close the current device. Under the BIOS this does nothing much.
508 movb dev_state
, al
! State is
"closed"
511 ! Reset the disks if needed. Minix may have messed things up.
513 cmpb dev_state
, #0 ! Need reset if dev_state < 0
515 xorb ah
, ah
! Reset
(ah
= 0)
516 movb dl
, #0x80 ! All disks
518 movb dev_state
, #0 ! State is "closed"
521 ! int dev_boundary
(u32_t sector
);
522 ! True if
a sector is on
a boundary
, i.e. sector
% sectors
== 0.
523 .define _dev_boundary
527 mov ax
, 4(bx
) ! divide high half of sector number
529 mov ax
, 2(bx
) ! divide low half of sector number
530 div sectors
! dx
= sector
% sectors
531 sub dx
, #1 ! CF = dx == 0
532 sbb ax
, ax
! ax
= -CF
533 neg ax
! ax
= (sector
% sectors
) == 0
536 ! int biosreadsectors
(u32_t bufaddr
, u32_t sector
, u8_t count
)
537 ! int writesectors
(u32_t bufaddr
, u32_t sector
, u8_t count
)
538 ! Read
/write several sectors from
/to disk
or floppy. The buffer must
539 ! be between
64K boundaries
! Count must fit in
a byte. The external
540 ! variables _device
, sectors
and secspcyl describe the disk
and its
541 ! geometry. Returns
0 for success
, otherwise the BIOS error code.
543 .define _biosreadsectors, _writesectors
547 movb
13(bp
), #0x03 ! Code for a disk write
552 movb
13(bp
), #0x02 ! Code for a disk read
556 cmpb dev_state
, #0 ! Device state?
558 call _dev_open
! Initialize
565 mov es
, dx
! es
:bx
= bufaddr
566 mov di
, #3 ! Execute 3 resets on floppy error
569 mov di
, #1 ! But only 1 reset on hard disk error
570 nohd
: cmpb
12(bp
), #0 ! count equals zero?
573 mov dx
, 10(bp
) ! dx
:ax
= abs sector. Divide it by sectors
/cyl
574 cmp dx
, #[1024*255*63-255]>>16 ! Near 8G limit?
577 cmp si
, _cddevice
! Is it
a CD?
578 je bigdisk
! CD
's need extended read.
579 div secspcyl ! ax = cylinder, dx = sector within cylinder
580 xchg ax, dx ! ax = sector within cylinder, dx = cylinder
581 movb ch, dl ! ch = low 8 bits of cylinder
582 divb sectors ! al = head, ah = sector (0-origin)
583 xorb dl, dl ! About to shift bits 8-9 of cylinder into dl
585 shr dx, #1 ! dl[6..7] = high cylinder
586 orb dl, ah ! dl[0..5] = sector (0-origin)
587 movb cl, dl ! cl[0..5] = sector, cl[6..7] = high cyl
588 incb cl ! cl[0..5] = sector (1-origin)
589 movb dh, al ! dh = head
590 movb dl, _device ! dl = device to use
591 movb al, sectors ! Sectors per track - Sector number (0-origin)
592 subb al, ah ! = Sectors left on this track
593 cmpb al, 12(bp) ! Compare with # sectors to transfer
594 jbe doit ! Can't go past the end of
a cylinder?
595 movb al
, 12(bp
) ! 12(bp
) < sectors left on this track
596 doit
: movb ah
, 13(bp
) ! Code for disk read
(0x02) or write
(0x03)
597 push ax
! Save al
= sectors to read
598 int
0x13 ! call the BIOS to do the transfer
599 pop cx
! Restore al in cl
602 mov si
, #ext_rw ! si = extended read/write parameter packet
604 movb
2(si
), cl
! Fill in
# blocks to transfer
605 mov
4(si
), bx
! Buffer address
= es
:bx
607 mov
8(si
), ax
! Starting block number
= dx
:ax
609 movb dl
, _device
! dl
= device to use
610 mov ax
, #0x4000 ! This, or-ed with 0x02 or 0x03 becomes
611 orb ah
, 13(bp
) ! extended read
(0x4200) or write
(0x4300)
616 movb al
, cl
! Restore al
= sectors read
617 addb bh
, al
! bx
+= 2 * al
* 256 (add bytes transferred
)
618 addb bh
, al
! es
:bx
= where next sector is located
619 add 8(bp
), ax
! Update address by sectors transferred
620 adc
10(bp
), #0 ! Don't forget high word
621 subb
12(bp
), al
! Decrement sector count by sectors transferred
622 jnz more
! Not all sectors have been transferred
623 done
: xorb ah
, ah
! No error here
!
625 ioerr
: cmpb ah
, #0x80 ! Disk timed out? (Floppy drive empty)
627 cmpb ah
, #0x03 ! Disk write protected?
629 dec di
! Do we allow another reset?
630 jl finish
! No
, report the error
631 xorb ah
, ah
! Code for
a reset
(0)
633 jnc more
! Succesful reset
, try request again
635 xorb ah
, ah
! ax
= error number
643 ! Extended read
/write commands require
a parameter packet.
645 .data1 0x10 ! Length of extended r/w packet
647 .data2 0 ! Blocks to transfer (to be filled in)
648 .data2 0 ! Buffer address offset (tbfi)
649 .data2 0 ! Buffer address segment (tbfi)
650 .data4 0 ! Starting block number low 32 bits (tbfi)
651 .data4 0 ! Starting block number high 32 bits
655 ! Read
a character from the keyboard
, and check for an expired timer.
656 ! A carriage return is changed into
a linefeed for UNIX compatibility.
660 xchg ax
, unchar
! Ungotten character?
664 ! hlt
! Play dead until interrupted
(see pause
())
665 movb ah
, #0x01 ! Keyboard status
667 jz
0f
! Nothing typed
668 xorb ah
, ah
! Read character from keyboard
671 0: mov dx
, line
! Serial line?
674 add dx
, #5 ! Line Status Register
676 testb al
, #0x01 ! Data Ready?
679 !add dx
, 0 ! Receive Buffer Register
680 inb dx
! Get character
682 0: call _expired
! Timer expired?
685 mov ax
, #ESC ! Return ESC
688 cmpb al
, #0x0D ! Carriage return?
690 movb al
, #0x0A ! Change to linefeed
691 nocr
: cmpb al
, #ESC ! Escape typed?
693 inc escape
! Set flag
694 noesc
: xorb ah
, ah
! ax
= al
698 ! Return
a character to undo
a getch
().
707 ! True if ESC has been typed.
710 movb ah
, #0x01 ! Keyboard status
712 jz escflg
! Keypress?
713 cmpb al
, #ESC ! Escape typed?
715 xorb ah
, ah
! Discard the escape
717 inc escape
! Set flag
719 xchg ax
, escape
! Escape typed flag
723 ! Write
a character in teletype mode. The putk synonym is
724 ! for the kernel printf function that uses it.
725 ! Newlines are automatically preceded by
a carriage return.
727 .define _putch, _putk
730 movb al
, 2(bx
) ! al
= character to
be printed
731 testb al
, al
! Kernel printf adds
a null char to flush queue
733 cmpb al
, #0x0A ! al = newline?
736 call putc
! putc
('\r')
737 movb al
, #0x0A ! Restore the '\n' and print it
738 putc
: movb ah
, #0x0E ! Print character in teletype mode
739 mov bx
, #0x0001 ! Page 0, foreground color
741 mov bx
, line
! Serial line?
744 push ax
! Save character to print
745 call _get_tick
! Current clock tick counter
747 add cx
, #2 ! Don't want to see it count twice
748 1: lea dx
, 5(bx
) ! Line Status Register
750 testb al
, #0x20 ! Transmitter Holding Register Empty?
753 cmp ax
, cx
! Clock ticked more than once?
755 0: pop ax
! Restore character to print
756 mov dx
, bx
! Transmit Holding Register
757 outb dx
! Send character down the serial line
761 ! Wait for an interrupt using the HLT instruction. This either saves
762 ! power
, or tells an x86 emulator that nothing is happening right now.
768 ! void set_mode
(unsigned mode
);
769 ! void clear_screen
(void
);
770 ! Set video mode
/ clear the screen.
771 .define _set_mode, _clear_screen
774 mov ax
, 2(bx
) ! Video mode
776 je modeok
! Mode already as requested?
780 mov es
, ax
! es
= Vector segment
782 movb ch
, ah
! Copy of the special flags
783 andb ah
, #0x0F ! Test bits 8-11, clear special flags
784 jnz xvesa
! VESA extended mode?
785 int
0x10 ! Reset video
(ah
= 0)
787 xvesa
: mov bx
, ax
! bx
= extended mode
788 mov ax
, #0x4F02 ! Reset video
790 md_480
: ! Basic video mode is set
, now build on it
791 testb ch
, #0x20 ! 480 scan lines requested?
793 mov dx
, #0x3CC ! Get CRTC port
796 testb al
, #1 ! Mono or color?
799 0: mov ax
, #0x110C ! Vertical sync end (also unlocks CR0-7)
801 mov ax
, #0x060B ! Vertical total
803 mov ax
, #0x073E ! (Vertical) overflow
805 mov ax
, #0x10EA ! Vertical sync start
807 mov ax
, #0x12DF ! Vertical display end
809 mov ax
, #0x15E7 ! Vertical blank start
811 mov ax
, #0x1604 ! Vertical blank end
814 movb dl
, #0xCC ! Misc output register (read)
816 movb dl
, #0xC2 ! (write)
817 andb al
, #0x0D ! Preserve clock select bits and color bit
818 orb al
, #0xE2 ! Set correct sync polarity
820 pop dx
! Index register still in dx
822 testb ch
, #0x40 ! 9x14 point font requested?
824 mov ax
, #0x1111 ! Load ROM 9 by 14 font
825 xorb
bl, bl ! Load block
0
827 testb ch
, #0x20 ! 480 scan lines?
829 mov ax
, #0x12DB ! VGA vertical display end
831 eseg movb
0x0484, #33 ! Tell BIOS the last line number
833 testb ch
, #0x80 ! 8x8 point font requested?
835 mov ax
, #0x1112 ! Load ROM 8 by 8 font
836 xorb
bl, bl ! Load block
0
838 testb ch
, #0x20 ! 480 scan lines?
840 mov ax
, #0x12DF ! VGA vertical display end
842 eseg movb
0x0484, #59 ! Tell BIOS the last line number
844 xor dx
, dx
! dl
= column
= 0, dh
= row
= 0
846 movb ah
, #0x02 ! Set cursor position
852 ! Out to the usual
[index
, data
] port pair that are common for VGA devices
853 ! dx
= port
, ah
= index
, al
= data.
865 restore_video
: ! To restore the video mode on exit
872 ! void serial_init
(int line
)
873 ! Initialize copying console I
/O to
a serial line.
877 mov dx
, 2(bx
) ! Line number
879 test dx
, dx
! Off if line number
< 0
883 mov ds
, ax
! Vector
and BIOS data segment
884 mov bx
, dx
! Line number
885 shl bx
, #1 ! Word offset
886 mov bx
, 0x0400(bx
) ! I
/O port for the given line
888 mov line
, bx
! Remember I
/O port
891 test bx
, bx
! I
/O port must
be nonzero
893 mov ax
, #0x00E3 ! 9600 N-8-1
894 int
0x14 ! Initialize serial line dx
895 lea dx
, 4(bx
) ! Modem Control Register
896 movb al
, #0x0B ! DTR, RTS, OUT2
900 ! u32_t get_tick
(void
);
901 ! Return the current value of the clock tick counter. This counter
902 ! increments
18.2 times per second. Poll it to do delays. Does
not
903 ! work on the original PC
, but works on the PC
/XT.
907 xorb ah
, ah
! Code for get tick count
910 mov dx
, cx
! dx
:ax
= cx
:dx
= tick count
915 ! Functions used to obtain info about the hardware. Boot uses this information
916 ! itself
, but will also pass them on to
a pure
386 kernel
, because one can
't
917 ! make BIOS calls from protected mode. The video type could probably be
918 ! determined by the kernel too by looking at the hardware, but there is a small
919 ! chance on errors that the monitor allows you to correct by setting variables.
921 .define _get_bus ! returns type of system bus
922 .define _get_video ! returns type of display
924 ! u16_t get_bus(void)
925 ! Return type of system bus, in order: XT, AT, MCA.
928 xor dx, dx ! Assume XT
929 cmp ax, #286 ! An AT has at least a 286
932 movb ah, #0xC0 ! Code for get configuration
934 jc got_bus ! Carry clear and ah = 00 if supported
938 movb al, 5(bx) ! Load feature byte #1
940 testb al, #0x02 ! Test bit 1 - "bus is Micro Channel"
943 testb al, #0x40 ! Test bit 6 - "2nd 8259 installed"
949 mov ax, dx ! Return bus code
950 mov bus, ax ! Keep bus code, A20 handler likes to know
953 ! u16_t get_video(void)
954 ! Return type of display, in order: MDA, CGA, mono EGA, color EGA,
955 ! mono VGA, color VGA.
957 mov ax, #0x1A00 ! Function 1A returns display code
958 int 0x10 ! al = 1A if supported
960 jnz no_dc ! No display code function supported
963 cmpb bl, #5 ! Is it a monochrome EGA?
966 cmpb bl, #4 ! Is it a color EGA?
969 cmpb bl, #7 ! Is it a monochrome VGA?
972 cmpb bl, #8 ! Is it a color VGA?
975 no_dc: movb ah, #0x12 ! Get information about the EGA
978 cmpb bl, #0x10 ! Did it come back as 0x10? (No EGA)
982 cmpb bh, #1 ! Is it monochrome?
987 no_ega: int 0x11 ! Get bit pattern for equipment
988 and ax, #0x30 ! Isolate color/mono field
990 jz got_video ! Is it an MDA?
991 mov ax, #1 ! No it's CGA
997 ! Functions to leave the boot monitor.
998 .define _bootstrap ! Call another bootstrap
999 .define _minix ! Call Minix
1001 ! void _bootstrap
(int device
, struct part_entry
*entry
)
1002 ! Call another bootstrap routine to boot MS-DOS for instance.
(No real
1003 ! need for that anymore
, now that you can format floppies under Minix
).
1004 ! The bootstrap must have been loaded at BOOTSEG from
"device".
1008 movb dl
, 2(bx
) ! Device to boot from
1009 mov si
, 4(bx
) ! ds
:si
= partition table entry
1011 mov es
, ax
! Vector segment
1012 mov di
, #BUFFER ! es:di = buffer in low core
1013 mov cx
, #PENTRYSIZE ! cx = size of partition table entry
1014 rep movsb
! Copy the entry to low core
1015 mov si
, #BUFFER ! es:si = partition table entry
1016 mov ds
, ax
! Some bootstraps need zero segment registers
1019 mov sp
, #BOOTOFF ! This should do it
1021 jmpf BOOTOFF
, 0 ! Back to where the BIOS loads the boot code
1023 ! void minix
(u32_t koff
, u32_t kcs
, u32_t kds
,
1024 ! char
*bootparams
, size_t paramsize
, u32_t aout
);
1028 mov bp
, sp
! Pointer to arguments
1030 mov dx
, #0x03F2 ! Floppy motor drive control bits
1031 movb al
, #0x0C ! Bits 4-7 for floppy 0-3 are off
1032 outb dx
! Kill the motors
1034 xor ax
, ax
! Vector
& BIOS data segments
1036 andb
0x043F, #0xF0 ! Clear diskette motor status bits of BIOS
1038 cli ! No more interruptions
1040 test _k_flags
, #K_I386 ! Switch to 386 mode?
1043 ! Call Minix in real mode.
1045 test _k_flags
, #K_MEML ! New memory arrangements?
1047 push
22(bp
) ! Address of
a.out headers
1050 push
18(bp
) ! # bytes of boot parameters
1051 push
16(bp
) ! Address of boot parameters
1053 test _k_flags
, #K_RET ! Can the kernel return?
1055 xor dx
, dx
! If little ext mem then monitor
not preserved
1057 cmp _mon_return
, ax
! Minix can return to the monitor?
1059 mov dx
, cs
! Monitor far return address
1061 0: push dx
! Push monitor far return address
or zero
1068 push dx
! Kernel code segment
1069 push
4(bp
) ! Kernel code offset
1073 mov ds
, dx
! Kernel data segment
1074 mov es
, dx
! Set es to kernel data too
1075 retf
! Make
a far call to the kernel
1077 ! Call Minix in
386 mode.
1079 cseg mov cs_real-
2, cs
! Patch CS
and DS into the instructions that
1080 cseg mov ds_real-
2, ds
! reload them when switching back to real mode
1081 .data1 0x0F,0x20,0xC0 ! mov eax, cr0
1082 orb al
, #0x01 ! Set PE (protection enable) bit
1084 mov msw
, ax
! Save as protected mode machine status word
1086 mov dx
, ds
! Monitor ds
1087 mov ax
, #p_gdt ! dx:ax = Global descriptor table
1089 mov p_gdt_desc+
2, ax
1090 movb p_gdt_desc+
4, dl
! Set base of global descriptor table
1093 mov dx
, 14(bp
) ! Kernel ds
(absolute address
)
1095 movb p_ds_desc+
4, dl
! Set base of kernel data segment
1097 mov dx
, ss
! Monitor ss
1098 xor ax
, ax
! dx
:ax
= Monitor stack segment
1099 call seg2abs
! Minix starts with the stack of the monitor
1101 movb p_ss_desc+
4, dl
1104 mov dx
, 10(bp
) ! Kernel cs
(absolute address
)
1106 movb p_cs_desc+
4, dl
1108 mov dx
, cs
! Monitor cs
1109 xor ax
, ax
! dx
:ax
= Monitor code segment
1111 mov p_mcs_desc+
2, ax
1112 movb p_mcs_desc+
4, dl
1115 test _k_flags
, #K_INT86 ! Generic INT86 support?
1117 push
#int86 ! Far address to INT86 support
1119 0: push
#bios13 ! Far address to BIOS int 13 support
1121 test _k_flags
, #K_MEML ! New memory arrangements?
1124 push
20(bp
) ! Address of
a.out headers
1127 push
18(bp
) ! 32 bit size of parameters on stack
1129 push
16(bp
) ! 32 bit address of parameters
(ss relative
)
1131 test _k_flags
, #K_RET ! Can the kernel return?
1134 push
#ret386 ! Monitor far return address
1140 push
4(bp
) ! 32 bit far address to kernel entry point
1142 call real2prot
! Switch to protected mode
1143 mov ax
, #DS_SELECTOR ! Kernel data
1145 mov ax
, #ES_SELECTOR ! Flat 4 Gb
1147 .data1 o32 ! Make a far call to the kernel
1150 ! Minix-
86 returns here on
a halt
or reboot.
1152 mov _reboot_code+
0, ax
1153 mov _reboot_code+
2, dx
! Return value
(obsolete method
)
1156 ! Minix-
386 returns here on
a halt
or reboot.
1159 mov _reboot_code
, ax
! Return value
(obsolete method
)
1160 call prot2real
! Switch to real mode
1163 mov sp
, bp
! Pop parameters
1164 sti
! Can take interrupts again
1166 call _get_video
! MDA
, CGA
, EGA
, ...
1167 movb dh
, #24 ! dh = row 24
1168 cmp ax
, #2 ! At least EGA?
1169 jb is25
! Otherwise
25 rows
1171 xor ax
, ax
! Vector
& BIOS data segments
1173 movb dh
, 0x0484 ! Number of rows on display minus one
1176 xorb dl
, dl
! dl
= column
0
1177 xorb bh
, bh
! Page
0
1178 movb ah
, #0x02 ! Set cursor position
1181 movb dev_state
, #-1 ! Minix may have upset the disks, must reset.
1182 call serial_init
! Likewise with our serial console
1190 movb ah
, #0x02 ! Get real-time clock time (from CMOS clock)
1192 jc tryclk
! Carry set
, not running
or being updated
1193 movb al
, ch
! ch
= hour in BCD
1194 call bcd
! al
= (al
>> 4) * 10 + (al
& 0x0F)
1195 mulb c60
! 60 minutes in an hour
1196 mov bx
, ax
! bx
= hour
* 60
1197 movb al
, cl
! cl
= minutes in BCD
1199 add bx
, ax
! bx
= hour
* 60 + minutes
1200 movb al
, dh
! dh
= seconds in BCD
1202 xchg ax
, bx
! ax
= hour
* 60 + minutes
, bx
= seconds
1203 mul c60
! dx-ax
= (hour
* 60 + minutes
) * 60
1205 adc dx
, #0 ! dx-bx = seconds since midnight
1210 add dx
, bx
! dx-ax
= dx-bx
* (0x1800B0 / (2*2*2*2*5))
1211 mov cx
, ax
! (0x1800B0 = ticks per day of BIOS clock
)
1216 div c1080
! cx-ax
= dx-ax
/ (24*60*60 / (2*2*2*2*5))
1217 mov dx
, ax
! cx-dx
= ticks since midnight
1218 movb ah
, #0x01 ! Set system time
1223 ret
! Return to monitor as if nothing much happened
1225 ! Transform BCD number in al to
a regular value in ax.
1229 .data1 0xD5,10 ! aad ! ax = (al >> 4) * 10 + (al & 0x0F)
1230 ret
! (BUG
: assembler messes up aad
& aam
!)
1232 ! Support function for Minix-
386 to make
a BIOS int
13 call
(disk I
/O
).
1236 sti
! Enable interrupts
1238 mov ax
, 8(bp
) ! Load parameters
1243 int
0x13 ! Make the BIOS call
1244 mov
8(bp
), ax
! Save results
1250 cli ! Disable interrupts
1252 mov ax
, #DS_SELECTOR ! Kernel data
1255 retf
! Return to the kernel
1257 ! Support function for Minix-
386 to make an
8086 interrupt call.
1264 mov es
, ax
! Vector
& BIOS data segments
1266 eseg mov
0x046C, ax
! Clear BIOS clock tick counter
1268 sti
! Enable interrupts
1270 movb al
, #0xCD ! INT instruction
1271 movb ah
, 8(bp
) ! Interrupt number?
1273 jnz
0f
! Nonzero if INT
, otherwise far call
1275 push
#intret+2 ! Far return address
1277 push
12(bp
) ! Far driver address
1278 mov ax
, #0x90CB ! RETF; NOP
1280 cseg
cmp ax
, intret
! Needs to
be changed?
1281 je
0f
! If
not then avoid
a huge I-cache stall
1282 cseg mov intret
, ax
! Patch
'INT n' or 'RETF; NOP' into code
1283 jmp
.+2 ! Clear instruction queue
1285 mov ds
, 16(bp
) ! Load parameters
1302 intret
: int
0xFF ! Do the interrupt
or far call
1304 .data1 o32 ! Save results
1310 pop
8+8(bp
) ! eflags
1328 cli ! Disable interrupts
1331 mov ds
, ax
! Vector
& BIOS data segments
1333 mov cx
, 0x046C ! Collect lost clock ticks in ecx
1336 mov ds
, ax
! Restore monitor ds
1338 mov ax
, #DS_SELECTOR ! Kernel data
1341 retf
! Return to the kernel
1343 ! Switch from real to protected mode.
1345 movb ah
, #0x02 ! Code for A20 enable
1348 lgdt p_gdt_desc
! Global descriptor table
1350 mov ax
, pdbr
! Load page directory base register
1351 .data1 0x0F,0x22,0xD8 ! mov cr3, eax
1352 .data1 0x0F,0x20,0xC0 ! mov eax, cr0
1354 xchg ax
, msw
! Exchange real mode msw for protected mode msw
1355 .data1 0x0F,0x22,0xC0 ! mov cr0, eax
1356 jmpf cs_prot
, MCS_SELECTOR
! Set code segment selector
1358 mov ax
, #SS_SELECTOR ! Set data selectors
1364 ! Switch from protected to real mode.
1366 lidt p_idt_desc
! Real mode interrupt vectors
1367 .data1 0x0F,0x20,0xD8 ! mov eax, cr3
1369 mov pdbr
, ax
! Save page directory base register
1370 .data1 0x0F,0x20,0xC0 ! mov eax, cr0
1372 xchg ax
, msw
! Exchange protected mode msw for real mode msw
1373 .data1 0x0F,0x22,0xC0 ! mov cr0, eax
1374 jmpf cs_real
, 0xDEAD ! Reload cs register
1378 mov ds
, ax
! Reload data segment registers
1382 xorb ah
, ah
! Code for A20 disable
1385 ! Enable
(ah
= 0x02) or disable
(ah
= 0x00) the A20 address line.
1387 cmp bus
, #2 ! PS/2 bus?
1390 movb al
, #0xD1 ! Tell keyboard that a command is coming
1393 movb al
, #0xDD ! 0xDD = A20 disable code if ah = 0x00
1394 orb al
, ah
! 0xDF = A20 enable code if ah
= 0x02
1397 movb al
, #0xFF ! Pulse output port
1399 call kb_wait
! Wait for the A20 line to settle down
1403 testb al
, #0x02 ! Keyboard input buffer full?
1404 jnz kb_wait
! If so
, wait
1407 gate_PS_A20
: ! The PS
/2 can twiddle A20 using port
A
1408 inb
0x92 ! Read port
A
1410 orb al
, ah
! Set A20 bit to the required state
1411 outb
0x92 ! Write port
A
1412 jmp
.+2 ! Small delay
1413 A20ok
: inb
0x92 ! Check port
A
1415 cmpb al
, ah
! A20 line settled down to the new state?
1416 jne A20ok
! If
not then wait
1419 ! void int15
(bios_env_t
*ep
)
1420 ! Do an
"INT 15" call
, primarily for APM
(Power Management
).
1423 push si
! Save callee-save register si
1426 mov ax
, (si
) ! ep-
>ax
1427 mov bx
, 2(si
) ! ep-
>bx
1428 mov cx
, 4(si
) ! ep-
>cx
1429 int
0x15 ! INT
0x15 BIOS call
1431 mov
(si
), ax
! ep-
>ax
1432 mov
2(si
), bx
! ep-
>bx
1433 mov
4(si
), cx
! ep-
>cx
1434 pop
6(si
) ! ep-
>flags
1438 ! void scan_keyboard
(void
)
1439 ! Read keyboard character. Needs to
be done in case one is waiting.
1440 .define _scan_keyboard
1452 .ascii "(null)\0" ! Just in case someone follows a null pointer
1454 c60
: .data2 60 ! Constants for MUL and DIV
1457 c19663
: .data2 19663
1459 ! Global descriptor tables.
1460 UNSET
= 0 ! Must
be computed
1462 ! For
"Extended Memory Block Move".
1466 .data2 0x0000, 0x0000
1467 .data1 0x00, 0x00, 0x00, 0x00
1469 ! Descriptor for this descriptor table
1471 .data1 UNSET, 0x00, 0x00, 0x00
1473 ! Source segment descriptor
1474 .data2 0xFFFF, UNSET
1475 .data1 UNSET, 0x92, 0x00, 0x00
1477 ! Destination segment descriptor
1478 .data2 0xFFFF, UNSET
1479 .data1 UNSET, 0x92, 0x00, 0x00
1481 ! BIOS segment descriptor
(scratch for int
0x15)
1483 .data1 UNSET, UNSET, UNSET, UNSET
1485 ! BIOS stack segment descriptor
(scratch for int
0x15)
1487 .data1 UNSET, UNSET, UNSET, UNSET
1489 ! Protected mode descriptor table.
1493 .data2 0x0000, 0x0000
1494 .data1 0x00, 0x00, 0x00, 0x00
1496 ! Descriptor for this descriptor table
1498 .data1 UNSET, 0x00, 0x00, 0x00
1500 ! Real mode interrupt descriptor table descriptor
1501 .data2 0x03FF, 0x0000
1502 .data1 0x00, 0x00, 0x00, 0x00
1504 ! Kernel data segment descriptor
(4 Gb flat
)
1505 .data2 0xFFFF, UNSET
1506 .data1 UNSET, 0x92, 0xCF, 0x00
1508 ! Physical memory descriptor
(4 Gb flat
)
1509 .data2 0xFFFF, 0x0000
1510 .data1 0x00, 0x92, 0xCF, 0x00
1512 ! Monitor data segment descriptor
(64 kb flat
)
1513 .data2 0xFFFF, UNSET
1514 .data1 UNSET, 0x92, 0x00, 0x00
1516 ! Kernel code segment descriptor
(4 Gb flat
)
1517 .data2 0xFFFF, UNSET
1518 .data1 UNSET, 0x9A, 0xCF, 0x00
1520 ! Monitor code segment descriptor
(64 kb flat
)
1521 .data2 0xFFFF, UNSET
1522 .data1 UNSET, 0x9A, 0x00, 0x00
1525 .comm old_vid_mode, 2 ! Video mode at startup
1526 .comm cur_vid_mode, 2 ! Current video mode
1527 .comm dev_state, 2 ! Device state: reset (-1), closed (0), open (1)
1528 .comm sectors, 2 ! # sectors of current device
1529 .comm secspcyl, 2 ! (Sectors * heads) of current device
1530 .comm msw, 4 ! Saved machine status word (cr0)
1531 .comm pdbr, 4 ! Saved page directory base register (cr3)
1532 .comm escape, 2 ! Escape typed?
1533 .comm bus, 2 ! Saved return value of _get_bus
1534 .comm unchar, 2 ! Char returned by ungetch(c)
1535 .comm line, 2 ! Serial line I/O port to copy console I/O to.