source: trunk/minix/boot/doshead.s@ 9

Last change on this file since 9 was 9, checked in by Mattia Monga, 13 years ago

Minix 3.1.2a

File size: 34.4 KB
Line 
1! Doshead.s - DOS & BIOS support for boot.c Author: Kees J. Bot
2!
3!
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.
7!
8! This runs under MS-DOS as a .COM file. A .COM file is what Minix calls
9! a common I&D executable, except that the first 256 bytes contains DOS
10! thingies.
11!
12.sect .text; .sect .rom; .sect .data; .sect .bss
13
14 K_I386 = 0x0001 ! Call Minix in 386 mode
15 STACK = 16384 ! Number of bytes for the stack
16
17 DS_SELECTOR = 3*8 ! Kernel data selector
18 ES_SELECTOR = 4*8 ! Flat 4 Gb
19 SS_SELECTOR = 5*8 ! Monitor stack
20 CS_SELECTOR = 6*8 ! Kernel code
21 MCS_SELECTOR= 7*8 ! Monitor code
22
23 ESC = 0x1B ! Escape character
24
25! Imported variables and functions:
26.extern _caddr, _daddr, _runsize, _edata, _end ! Runtime environment
27.extern _k_flags ! Special kernel flags
28.extern _mem ! Free memory list
29.extern _vdisk ! Name of the virtual disk
30
31.sect .text
32
33.use16 ! Tell 386 assembler we're in 16-bit mode
34
35.define _PSP
36_PSP:
37 .space 256 ! Program Segment Prefix
38
39dosboot:
40 cld ! C compiler wants UP
41 xor ax, ax ! Zero
42 mov di, _edata ! Start of bss is at end of data
43 mov cx, _end ! End of bss (begin of heap)
44 sub cx, di ! Number of bss bytes
45 shr cx, 1 ! Number of words
46 rep stos ! Clear bss
47 cmp sp, _end+STACK
48 jb 0f
49 mov sp, _end+STACK ! "chmem" to 16 kb
500:
51
52! Are we called with the /U option?
53 movb cl, (_PSP+0x80) ! Argument byte count
54 xorb ch, ch
55 mov bx, _PSP+0x81 ! Argument string
560: jcxz notuflag
57 cmpb (bx), 0x20 ! Whitespace?
58 ja 1f
59 inc bx
60 dec cx
61 jmp 0b
621: cmp cx, 2 ! '/U' is two bytes
63 jne notuflag
64 cmpb (bx), 0x2F ! '/'?
65 jne notuflag
66 movb al, 1(bx)
67 andb al, ~0x20 ! Ignore case
68 cmpb al, 0x55 ! 'U'?
69 jne notuflag
70 jmp keepumb ! Go grab an UMB
71notuflag:
72
73! Remember the current video mode for restoration on exit.
74 movb ah, 0x0F ! Get current video mode
75 int 0x10
76 andb al, 0x7F ! Mask off bit 7 (no blanking)
77 movb (old_vid_mode), al
78 movb (cur_vid_mode), al
79
80! We require at least MS-DOS 3.0.
81 mov ax, 0x3000 ! Get DOS version
82 int 0x21
83 cmpb al, 3 ! DOS 3.0+ ?
84 jae dosok
85 push tellbaddos
86 call _printf
87 jmp quit
88.sect .rom
89tellbaddos: .ascii "MS-DOS 3.0 or better required\n\0"
90.sect .text
91dosok:
92
93! Find out how much "low" memory there is available, where it starts and
94! where it ends.
95 mov di, _mem ! di = memory list
96 mov ax, _PSP+0x80 ! From PSP:80 to next PSP is ours
97 mov dx, ds
98 call seg2abs
99 mov (di), ax
100 mov 2(di), dx ! mem[0].base = ds * 16 + 0x80
101 xor ax, ax
102 mov dx, (_PSP+2) ! First in-use segment far above us
103 call seg2abs
104 sub ax, (di)
105 sbb dx, 2(di) ! Minus base gives size
106 mov 4(di), ax
107 mov 6(di), dx ! mem[1].size = free low memory size
108
109! Give C code access to the code segment, data segment and the size of this
110! process.
111 xor ax, ax
112 mov dx, cs
113 call seg2abs
114 mov (_caddr+0), ax
115 mov (_caddr+2), dx
116 xor ax, ax
117 mov dx, ds
118 call seg2abs
119 mov (_daddr+0), ax
120 mov (_daddr+2), dx
121 mov ax, sp
122 mov dx, ss ! End of stack = end of program
123 call seg2abs
124 sub ax, (_caddr+0)
125 sbb dx, (_caddr+2) ! Minus start of our code
126 mov (_runsize+0), ax
127 mov (_runsize+2), dx ! Is our size
128
129! Patch the regular _getprocessor library routine to jump to 'getprocessor',
130! that checks if we happen to be in a V8086 straightjacket by returning '86'.
131 cseg movb (_getprocessor+0), 0xE9
132 mov ax, getprocessor
133 sub ax, _getprocessor+3
134 cseg mov (_getprocessor+1), ax
135
136! Grab the largest chunk of extended memory available.
137 call _getprocessor
138 cmp ax, 286 ! Only 286s and above have extended memory
139 jb no_ext
140 mov ax, 0x4300 ! XMS driver check
141 int 0x2F
142 cmpb al, 0x80 ! XMS driver exists?
143 je xmsthere
144get_ext: ! No driver, so can use all ext memory directly
145 call _getprocessor
146 cmp ax, 486 ! Assume 486s were the first to have >64M
147 jb small_ext ! (It helps to be paranoid when using the BIOS)
148big_ext:
149 mov ax, 0xE801 ! Code for get memory size for >64M
150 int 0x15 ! ax = mem at 1M per 1K, bx = mem at 16M per 64K
151 jnc got_ext
152small_ext:
153 movb ah, 0x88 ! Code for get extended memory size
154 clc ! Carry will stay clear if call exists
155 int 0x15 ! Returns size (in K) in ax for AT's
156 jc no_ext
157 test ax, ax ! An AT with no extended memory?
158 jz no_ext
159 xor bx, bx ! bx = mem above 16M per 64K = 0
160got_ext:
161 mov cx, ax ! cx = copy of ext mem at 1M
162 mov 10(di), 0x0010 ! mem[1].base = 0x00100000 (1M)
163 mul (c1024)
164 mov 12(di), ax ! mem[1].size = "ext mem at 1M" * 1024
165 mov 14(di), dx
166 test bx, bx
167 jz no_ext ! No more ext mem above 16M?
168 cmp cx, 15*1024 ! Chunks adjacent? (precisely 15M at 1M?)
169 je adj_ext
170 mov 18(di), 0x0100 ! mem[2].base = 0x01000000 (16M)
171 mov 22(di), bx ! mem[2].size = "ext mem at 16M" * 64K
172 jmp no_ext
173adj_ext:
174 add 14(di), bx ! Add ext mem above 16M to mem below 16M
175no_ext:
176 jmp gotxms
177
178xmsthere:
179 mov ax, 0x4310 ! Get XMS driver address
180 int 0x2F
181 mov (xms_driver+0), bx
182 mov (xms_driver+2), es
183 push ds
184 pop es
185 movb ah, 0x08 ! Query free extended memory
186 xorb bl, bl
187 callf (xms_driver)
188 testb bl, bl
189 jnz xmserr
190 push ax ! ax = size of largest block in kb
191 mul (c1024)
192 mov 12(di), ax
193 mov 14(di), dx ! mem[1].size = ax * 1024
194 pop dx ! dx = size of largest block in kb
195 movb ah, 0x09 ! Allocate XMS block of size dx
196 callf (xms_driver)
197 test ax, ax
198 jz xmserr
199 mov (xms_handle), dx ! Save handle
200 movb ah, 0x0C ! Lock XMS block (handle in dx)
201 callf (xms_driver)
202 test ax, ax
203 jz xmserr
204 mov 8(di), bx
205 mov 10(di), dx ! mem[1].base = Address of locked block
206gotxms:
207
208! If we're running in a DOS box then they're might be an Upper Memory Block
209! we can use. Every little bit helps when in real mode.
210 mov ax, 20(di)
211 or ax, 22(di) ! Can we use mem[2]?
212 jnz gotumb
213 mov dx, 0xFFFF ! dx = Maximum size, i.e. gimme all
214 call getumb ! Get UMB, dx = segment, cx = length
215 test cx, cx ! Did we get a block?
216 jz gotumb
217 xor ax, ax ! dx:ax = memory block
218 call seg2abs
219 mov 16(di), ax
220 mov 18(di), dx ! mem[2].base = memory block base
221 mov dx, cx
222 xor ax, ax ! dx:ax = length of memory block
223 call seg2abs
224 mov 20(di), ax
225 mov 22(di), dx ! mem[2].size = memory block length
226gotumb:
227
228! Set up an INT 24 "critical error" handler that returns "fail". This way
229! Minix won't suffer from "(A)bort, (R)etry, (I)nfluence with a large hammer?".
230 mov (0x007C), 0x03B0 ! movb al, 0x03 (fail code)
231 movb (0x007E), 0xCF ! iret
232 movb ah, 0x25 ! Set interrupt vector
233 mov dx, 0x007C ! ds:dx = ds:0x007C = interrupt handler
234 int 0x21
235
236! Time to switch to a higher level language (not much higher)
237 call _boot
238
239! void ..exit(int status)
240! Exit the monitor by returning to DOS.
241.define _exit, __exit, ___exit ! Make various compilers happy
242_exit:
243__exit:
244___exit:
245 mov dx, (xms_handle)
246 cmp dx, -1 ! Is there an ext mem block in use?
247 je nohandle
248 movb ah, 0x0D ! Unlock extended memory block
249 callf (xms_driver)
250 mov dx, (xms_handle)
251 movb ah, 0x0A ! Free extended memory block
252 callf (xms_driver)
253nohandle:
254 call restore_video
255 pop ax
256 pop ax ! Return code in al
257 movb ah, 0x4C ! Terminate with return code
258 int 0x21
259
260quit: ! exit(1)
261 movb al, 1
262 push ax
263 call _exit
264
265xmserr:
266 xorb bh, bh
267 push bx
268 push tellxmserr
269 call _printf
270 jmp quit
271.sect .rom
272tellxmserr: .ascii "Extended memory problem, error 0x%02x\n\0"
273.sect .text
274
275! int getprocessor(void)
276! Prefix for the regular _getprocessor call that first checks if we're
277! running in a virtual 8086 box.
278getprocessor:
279 push sp ! Is pushed sp equal to sp?
280 pop ax
281 cmp ax, sp
282 jne gettrueproc ! If not then it's a plain 8086 or 80186
283 .data1 0x0F,0x01,0xE0 ! Use old 286 SMSW instruction to get the MSW
284 testb al, 0x01 ! Protected mode enabled?
285 jz gettrueproc ! If not then a 286 or better in real mode
286 mov ax, 86 ! Forget fancy tricks, say it's an 8086
287 ret
288gettrueproc: ! Get the true processor type
289 push bp ! _getprocessor prologue that is patched over.
290 mov bp, sp
291 jmp _getprocessor+3
292
293! Try to get an Upper Memory Block under MS-DOS 5+. Try to get one up to size
294! dx, return segment of UMB found in dx and size in paragraphs in cx.
295getumb:
296 xor cx, cx ! Initially nothing found
297 mov ax, 0x3000 ! Get DOS version
298 int 0x21
299 cmpb al, 5 ! MS-DOS 5.0 or better?
300 jb retumb
301 mov ax, 0x544D ! Get UMB kept by BOOT /U
302 int 0x15 ! Returns dx = segment, cx = size
303 jc 0f
304 cmp ax, 0x4D54 ! Carry clear and ax byte swapped?
305 je retumb
3060: mov ax, 0x5802 ! Get UMB link state
307 int 0x21
308 xorb ah, ah
309 push ax ! Save UMB link state
310 mov ax, 0x5803 ! Set UMB link state
311 mov bx, 0x0001 ! Add UMBs to DOS memory chain
312 int 0x21
313 mov ax, 0x5800 ! Get memory allocation strategy
314 int 0x21
315 push ax ! Save allocation strategy
316 mov ax, 0x5801 ! Set memory allocation strategy
317 mov bx, 0x0080 ! First fit, try high then low memory
318 int 0x21
319 movb ah, 0x48 ! Allocate memory
320 mov bx, dx ! Number of paragraphs wanted
321 int 0x21 ! Fails with bx = size of largest
322 jnc 0f ! Succeeds with ax = allocated block
323 test bx, bx ! Is there any?
324 jz no_umb
325 movb ah, 0x48 ! Allocate memory
326 int 0x21
327 jc no_umb ! Did we get some?
3280: mov dx, ax ! dx = segment
329 mov cx, bx ! cx = size
330no_umb: mov ax, 0x5801 ! Set memory allocation strategy
331 pop bx ! bx = saved former strategy
332 int 0x21
333 mov ax, 0x5803 ! Set UMB link state
334 pop bx ! bx = saved former link state
335 int 0x21
336retumb: ret
337
338! 'BOOT /U' instructs this program to grab the biggest available UMB and to
339! sit on it until the next invocation of BOOT wants it back. These shenanigans
340! are necessary because Windows 95 keeps all UMBs to itself unless you get hold
341! of them first.
342 umb = 0x80 ! UMB base and size
343 old15 = 0x84 ! Old 15 interrupt vector
344 new15 = 0x88 ! New 15 interrupt handler
345keepumb:
346 mov ax, 0x544D ! "Keep UMB" handler already present?
347 int 0x15
348 jc 0f
349 cmp ax, 0x4D54
350 je exitumb ! Already present, so quit
3510:
352 mov si, new15start
353 mov di, new15
354 mov cx, new15end
355 sub cx, si
356 rep movsb ! Copy handler into place
357 add di, 15
358 movb cl, 4
359 shr di, cl ! di = first segment above handler
360 mov cx, cs
361 cmp cx, 0xA000 ! Are we loaded high perchance?
362 jb nothigh
363werehigh:
364 add cx, di
365 mov (umb+0), cx ! Use my own memory as the UMB to keep
366 mov ax, (_PSP+2) ! Up to the next in-use segment
367 sub ax, dx ! ax = size of my free memory
368 cmp ax, 0x1000 ! At least 64K?
369 jb exitumb ! Don't bother if less
370 mov (umb+2), 0x1000 ! Size of UMB
371 add di, 0x1000 ! Keep my code plus 64K when TSR
372 jmp hook15
373nothigh:
374 mov dx, 0x1000
375 call getumb ! Grab an UMB of at most 64K
376 cmp cx, 0x1000 ! Did we get 64K?
377 jb exitumb ! Otherwise don't bother
378 mov (umb+0), dx
379 mov (umb+2), cx
380hook15:
381 mov ax, 0x3515 ! Get interrupt vector
382 int 0x21
383 mov (old15+0), bx
384 mov (old15+2), es ! Old 15 interrupt
385 mov ax, 0x2515 ! Set interrupt vector
386 mov dx, new15 ! ds:dx = new 15 handler
387 int 0x21
388 mov ax, 0x3100 ! Terminate and stay resident
389 mov dx, di ! dx = di = paragraphs we keep
390 int 0x21
391exitumb:
392 mov ax, 0x4C00 ! exit(0)
393 int 0x21
394
395new15start: ! New interrupt 15 handler
396 pushf
397 cmp ax, 0x544D ! Is it my call?
398 je my15
399 popf
400 cseg jmpf (old15) ! No, continue with old 15
401my15: popf
402 push bp
403 mov bp, sp
404 andb 6(bp), ~0x01 ! clear carry, call will succeed
405 xchgb al, ah ! ax = 4D54, also means call works
406 cseg mov dx, (umb+0) ! dx = base of UMB
407 cseg mov cx, (umb+2) ! cx = size of UMB
408 pop bp
409 iret ! return to caller
410new15end:
411
412! u32_t mon2abs(void *ptr)
413! Address in monitor data to absolute address.
414.define _mon2abs
415_mon2abs:
416 mov bx, sp
417 mov ax, 2(bx) ! ptr
418 mov dx, ds ! Monitor data segment
419 !jmp seg2abs
420
421seg2abs: ! Translate dx:ax to the 32 bit address dx-ax
422 push cx
423 movb ch, dh
424 movb cl, 4
425 shl dx, cl
426 shrb ch, cl ! ch-dx = dx << 4
427 add ax, dx
428 adcb ch, 0 ! ch-ax = ch-dx + ax
429 movb dl, ch
430 xorb dh, dh ! dx-ax = ch-ax
431 pop cx
432 ret
433
434abs2seg: ! Translate the 32 bit address dx-ax to dx:ax
435 push cx
436 movb ch, dl
437 mov dx, ax ! ch-dx = dx-ax
438 and ax, 0x000F ! Offset in ax
439 movb cl, 4
440 shr dx, cl
441 shlb ch, cl
442 orb dh, ch ! dx = ch-dx >> 4
443 pop cx
444 ret
445
446! void raw_copy(u32_t dstaddr, u32_t srcaddr, u32_t count)
447! Copy count bytes from srcaddr to dstaddr. Don't do overlaps.
448! Also handles copying words to or from extended memory.
449.define _raw_copy
450_raw_copy:
451 push bp
452 mov bp, sp
453 push si
454 push di ! Save C variable registers
455copy:
456 cmp 14(bp), 0
457 jnz bigcopy
458 mov cx, 12(bp)
459 jcxz copydone ! Count is zero, end copy
460 cmp cx, 0xFFF0
461 jb smallcopy
462bigcopy:mov cx, 0xFFF0 ! Don't copy more than about 64K at once
463smallcopy:
464 push cx ! Save copying count
465 mov ax, 4(bp)
466 mov dx, 6(bp)
467 cmp dx, 0x0010 ! Copy to extended memory?
468 jae ext_copy
469 cmp 10(bp), 0x0010 ! Copy from extended memory?
470 jae ext_copy
471 call abs2seg
472 mov di, ax
473 mov es, dx ! es:di = dstaddr
474 mov ax, 8(bp)
475 mov dx, 10(bp)
476 call abs2seg
477 mov si, ax
478 mov ds, dx ! ds:si = srcaddr
479 shr cx, 1 ! Words to move
480 rep movs ! Do the word copy
481 adc cx, cx ! One more byte?
482 rep movsb ! Do the byte copy
483 mov ax, ss ! Restore ds and es from the remaining ss
484 mov ds, ax
485 mov es, ax
486 jmp copyadjust
487ext_copy:
488 mov (x_dst_desc+2), ax
489 movb (x_dst_desc+4), dl ! Set base of destination segment
490 mov ax, 8(bp)
491 mov dx, 10(bp)
492 mov (x_src_desc+2), ax
493 movb (x_src_desc+4), dl ! Set base of source segment
494 mov si, x_gdt ! es:si = global descriptor table
495 shr cx, 1 ! Words to move
496 movb ah, 0x87 ! Code for extended memory move
497 int 0x15
498copyadjust:
499 pop cx ! Restore count
500 add 4(bp), cx
501 adc 6(bp), 0 ! srcaddr += copycount
502 add 8(bp), cx
503 adc 10(bp), 0 ! dstaddr += copycount
504 sub 12(bp), cx
505 sbb 14(bp), 0 ! count -= copycount
506 jmp copy ! and repeat
507copydone:
508 pop di
509 pop si ! Restore C variable registers
510 pop bp
511 ret
512
513! u16_t get_word(u32_t addr);
514! void put_word(u32_t addr, u16_t word);
515! Read or write a 16 bits word at an arbitrary location.
516.define _get_word, _put_word
517_get_word:
518 mov bx, sp
519 call gp_getaddr
520 mov ax, (bx) ! Word to get from addr
521 jmp gp_ret
522_put_word:
523 mov bx, sp
524 push 6(bx) ! Word to store at addr
525 call gp_getaddr
526 pop (bx) ! Store the word
527 jmp gp_ret
528gp_getaddr:
529 mov ax, 2(bx)
530 mov dx, 4(bx)
531 call abs2seg
532 mov bx, ax
533 mov ds, dx ! ds:bx = addr
534 ret
535gp_ret:
536 push es
537 pop ds ! Restore ds
538 ret
539
540! void relocate(void);
541! After the program has copied itself to a safer place, it needs to change
542! the segment registers. Caddr has already been set to the new location.
543.define _relocate
544_relocate:
545 pop bx ! Return address
546 mov ax, (_caddr+0)
547 mov dx, (_caddr+2)
548 call abs2seg
549 mov cx, dx ! cx = new code segment
550 mov ax, cs ! Old code segment
551 sub ax, cx ! ax = -(new - old) = -Moving offset
552 mov dx, ds
553 sub dx, ax
554 mov ds, dx ! ds += (new - old)
555 mov es, dx
556 mov ss, dx
557 xor ax, ax
558 call seg2abs
559 mov (_daddr+0), ax
560 mov (_daddr+2), dx ! New data address
561 push cx ! New text segment
562 push bx ! Return offset of this function
563 retf ! Relocate
564
565! void *brk(void *addr)
566! void *sbrk(size_t incr)
567! Cannot fail implementations of brk(2) and sbrk(3), so we can use
568! malloc(3). They reboot on stack collision instead of returning -1.
569.sect .data
570 .align 2
571break: .data2 _end ! A fake heap pointer
572.sect .text
573.define _brk, __brk, _sbrk, __sbrk
574_brk:
575__brk: ! __brk is for the standard C compiler
576 xor ax, ax
577 jmp sbrk ! break= 0; return sbrk(addr);
578_sbrk:
579__sbrk:
580 mov ax, (break) ! ax= current break
581sbrk: push ax ! save it as future return value
582 mov bx, sp ! Stack is now: (retval, retaddr, incr, ...)
583 add ax, 4(bx) ! ax= break + increment
584 mov (break), ax ! Set new break
585 lea dx, -1024(bx) ! sp minus a bit of breathing space
586 cmp dx, ax ! Compare with the new break
587 jb heaperr ! Suffocating noises
588 pop ax ! Return old break (0 for brk)
589 ret
590heaperr:push nomem
591 call _printf
592 call quit
593.sect .rom
594nomem: .ascii "\nOut of memory\n\0"
595.sect .text
596
597! int dev_open(void);
598! Open file 'vdisk' to use as the Minix virtual disk. Store handle in
599! vfd. Returns 0 for success, otherwise the DOS error code.
600.define _dev_open
601_dev_open:
602 call _dev_close ! If already open then first close
603 mov dx, (_vdisk) ! ds:dx = Address of file name
604 mov ax, 0x3D22 ! Open file read-write & deny write
605 int 0x21
606 jnc opok ! Open succeeded?
607 cmp ax, 5 ! Open failed, "access denied"?
608 jne opbad
609 mov ax, 0x3D40 ! Open file read-only
610 int 0x21
611 jc opbad
612opok: mov (vfd), ax ! File handle to open file
613 xor ax, ax ! Zero for success
614opbad: ret
615
616! int dev_close(void);
617! Close the dos virtual disk.
618.define _dev_close
619_dev_close:
620 mov bx, -1
621 cmp (vfd), bx ! Already closed?
622 je 1f
623 movb ah, 0x3E ! Close file
624 xchg bx, (vfd) ! bx = vfd; vfd = -1;
625 int 0x21
626 jc 0f
6271: xor ax, ax
6280: ret
629
630! int dev_boundary(u32_t sector);
631! Returns false; files have no visible boundaries.
632.define _dev_boundary
633_dev_boundary:
634 xor ax, ax
635 ret
636
637! int readsectors(u32_t bufaddr, u32_t sector, u8_t count)
638! int writesectors(u32_t bufaddr, u32_t sector, u8_t count)
639! Read/write several sectors from/to the Minix virtual disk. Count
640! must fit in a byte. The external variable vfd is the file handle.
641! Returns 0 for success, otherwise the DOS error code.
642!
643.define _readsectors, _writesectors
644_writesectors:
645 push bp
646 mov bp, sp
647 movb 13(bp), 0x40 ! Code for a file write
648 jmp rwsec
649_readsectors:
650 push bp
651 mov bp, sp
652 movb 13(bp), 0x3F ! Code for a file read
653rwsec:
654 cmp (vfd), -1 ! Currently closed?
655 jne 0f
656 call _dev_open ! Open file if needed
657 test ax, ax
658 jnz rwerr
6590: mov dx, 8(bp)
660 mov bx, 10(bp) ! bx-dx = Sector number
661 mov cx, 9
662mul512: shl dx, 1
663 rcl bx, 1 ! bx-dx *= 512
664 loop mul512
665 mov cx, bx ! cx-dx = Byte position in file
666 mov bx, (vfd) ! bx = File handle
667 mov ax, 0x4200 ! Lseek absolute
668 int 0x21
669 jb rwerr
670 mov bx, (vfd) ! bx = File handle
671 mov ax, 4(bp)
672 mov dx, 6(bp) ! dx-ax = Address to transfer data to/from
673 call abs2seg
674 mov ds, dx
675 mov dx, ax ! ds:dx = Address to transfer data to/from
676 xorb cl, cl
677 movb ch, 12(bp) ! ch = Number of sectors to transfer
678 shl cx, 1 ! cx = Number of bytes to transfer
679 push cx ! Save count
680 movb ah, 13(bp) ! Read or write
681 int 0x21
682 pop cx ! Restore count
683 push es
684 pop ds ! Restore ds
685 jb rwerr
686 cmp ax, cx ! All bytes transferred?
687 je rwall
688 mov ax, 0x05 ! The DOS code for "I/O error", but different
689 jmp rwerr
690rwall: call wheel ! Display tricks
691 xor ax, ax
692rwerr: pop bp
693 ret
694
695! int getch(void);
696! Read a character from the keyboard, and check for an expired timer.
697! A carriage return is changed into a linefeed for UNIX compatibility.
698.define _getch
699_getch:
700 xor ax, ax
701 xchg ax, (unchar) ! Ungotten character?
702 test ax, ax
703 jnz gotch
704getch: hlt ! Play dead until interrupted (see pause())
705 movb ah, 0x01 ! Keyboard status
706 int 0x16
707 jnz press ! Keypress?
708 call _expired ! Timer expired?
709 test ax, ax
710 jz getch
711 mov ax, ESC ! Return ESC
712 ret
713press:
714 xorb ah, ah ! Read character from keyboard
715 int 0x16
716 cmpb al, 0x0D ! Carriage return?
717 jnz nocr
718 movb al, 0x0A ! Change to linefeed
719nocr: cmpb al, ESC ! Escape typed?
720 jne noesc
721 inc (escape) ! Set flag
722noesc: xorb ah, ah ! ax = al
723gotch: ret
724
725! int ungetch(void);
726! Return a character to undo a getch().
727.define _ungetch
728_ungetch:
729 mov bx, sp
730 mov ax, 2(bx)
731 mov (unchar), ax
732 ret
733
734! int escape(void);
735! True if ESC has been typed.
736.define _escape
737_escape:
738 movb ah, 0x01 ! Keyboard status
739 int 0x16
740 jz escflg ! Keypress?
741 cmpb al, ESC ! Escape typed?
742 jne escflg
743 xorb ah, ah ! Discard the escape
744 int 0x16
745 inc (escape) ! Set flag
746escflg: xor ax, ax
747 xchg ax, (escape) ! Escape typed flag
748 ret
749
750! int putch(int c);
751! Write a character in teletype mode. The putk synonym is
752! for the kernel printf function that uses it.
753! Newlines are automatically preceded by a carriage return.
754!
755.define _putch, _putk
756_putch:
757_putk: mov bx, sp
758 movb al, 2(bx) ! al = character to be printed
759 testb al, al ! Kernel printf adds a null char to flush queue
760 jz nulch
761 cmpb al, 0x0A ! al = newline?
762 jnz putc
763 movb al, 0x20 ! Erase wheel and do a carriage return
764 call plotc ! plotc(' ');
765nodirt: movb al, 0x0D
766 call putc ! putc('\r')
767 movb al, 0x0A ! Restore the '\n' and print it
768putc: movb ah, 0x0E ! Print character in teletype mode
769 mov bx, 0x0001 ! Page 0, foreground color
770 int 0x10 ! Call BIOS VIDEO_IO
771nulch: ret
772
773! |/-\|/-\|/-\|/-\|/-\ (playtime)
774wheel: mov bx, (gp)
775 movb al, (bx)
776 inc bx ! al = *gp++;
777 cmp bx, glyphs+4
778 jne 0f
779 mov bx, glyphs
7800: mov (gp), bx ! gp= gp == glyphs + 4 ? glyphs : gp;
781 !jmp plotc
782plotc: movb ah, 0x0A ! 0x0A = write character at cursor
783 mov bx, 0x0001 ! Page 0, foreground color
784 mov cx, 0x0001 ! Just one character
785 int 0x10
786 ret
787.sect .data
788 .align 2
789gp: .data2 glyphs
790glyphs: .ascii "|/-\\"
791.sect .text
792
793! void pause(void);
794! Wait for an interrupt using the HLT instruction. This either saves
795! power, or tells an x86 emulator that nothing is happening right now.
796.define _pause
797_pause:
798 hlt
799 ret
800
801! void set_mode(unsigned mode);
802! void clear_screen(void);
803! Set video mode / clear the screen.
804.define _set_mode, _clear_screen
805_set_mode:
806 mov bx, sp
807 mov ax, 2(bx) ! Video mode
808 cmp ax, (cur_vid_mode)
809 je modeok ! Mode already as requested?
810 mov (cur_vid_mode), ax
811_clear_screen:
812 mov ax, (cur_vid_mode)
813 andb ah, 0x7F ! Test bits 8-14, clear bit 15 (8x8 flag)
814 jnz xvesa ! VESA extended mode?
815 int 0x10 ! Reset video (ah = 0)
816 jmp mdset
817xvesa: mov bx, ax ! bx = extended mode
818 mov ax, 0x4F02 ! Reset video
819 int 0x10
820mdset: testb (cur_vid_mode+1), 0x80
821 jz setcur ! 8x8 font requested?
822 mov ax, 0x1112 ! Load ROM 8 by 8 double-dot patterns
823 xorb bl, bl ! Load block 0
824 int 0x10
825setcur: xor dx, dx ! dl = column = 0, dh = row = 0
826 xorb bh, bh ! Page 0
827 movb ah, 0x02 ! Set cursor position
828 int 0x10
829modeok: ret
830
831restore_video: ! To restore the video mode on exit
832 movb al, 0x20
833 call plotc ! Erase wheel
834 push (old_vid_mode)
835 call _set_mode
836 pop ax
837 ret
838
839! u32_t get_tick(void);
840! Return the current value of the clock tick counter. This counter
841! increments 18.2 times per second. Poll it to do delays. Does not
842! work on the original PC, but works on the PC/XT.
843.define _get_tick
844_get_tick:
845 xorb ah, ah ! Code for get tick count
846 int 0x1A
847 mov ax, dx
848 mov dx, cx ! dx:ax = cx:dx = tick count
849 ret
850
851
852! Functions used to obtain info about the hardware. Boot uses this information
853! itself, but will also pass them on to a pure 386 kernel, because one can't
854! make BIOS calls from protected mode. The video type could probably be
855! determined by the kernel too by looking at the hardware, but there is a small
856! chance on errors that the monitor allows you to correct by setting variables.
857
858.define _get_bus ! returns type of system bus
859.define _get_video ! returns type of display
860
861! u16_t get_bus(void)
862! Return type of system bus, in order: XT, AT, MCA.
863_get_bus:
864 call gettrueproc
865 xor dx, dx ! Assume XT
866 cmp ax, 286 ! An AT has at least a 286
867 jb got_bus
868 inc dx ! Assume AT
869 movb ah, 0xC0 ! Code for get configuration
870 int 0x15
871 jc got_bus ! Carry clear and ah = 00 if supported
872 testb ah, ah
873 jne got_bus
874 eseg movb al, 5(bx) ! Load feature byte #1
875 inc dx ! Assume MCA
876 testb al, 0x02 ! Test bit 1 - "bus is Micro Channel"
877 jnz got_bus
878 dec dx ! Assume AT
879 testb al, 0x40 ! Test bit 6 - "2nd 8259 installed"
880 jnz got_bus
881 dec dx ! It is an XT
882got_bus:
883 push ds
884 pop es ! Restore es
885 mov ax, dx ! Return bus code
886 mov (bus), ax ! Keep bus code, A20 handler likes to know
887 ret
888
889! u16_t get_video(void)
890! Return type of display, in order: MDA, CGA, mono EGA, color EGA,
891! mono VGA, color VGA.
892_get_video:
893 mov ax, 0x1A00 ! Function 1A returns display code
894 int 0x10 ! al = 1A if supported
895 cmpb al, 0x1A
896 jnz no_dc ! No display code function supported
897
898 mov ax, 2
899 cmpb bl, 5 ! Is it a monochrome EGA?
900 jz got_video
901 inc ax
902 cmpb bl, 4 ! Is it a color EGA?
903 jz got_video
904 inc ax
905 cmpb bl, 7 ! Is it a monochrome VGA?
906 jz got_video
907 inc ax
908 cmpb bl, 8 ! Is it a color VGA?
909 jz got_video
910
911no_dc: movb ah, 0x12 ! Get information about the EGA
912 movb bl, 0x10
913 int 0x10
914 cmpb bl, 0x10 ! Did it come back as 0x10? (No EGA)
915 jz no_ega
916
917 mov ax, 2
918 cmpb bh, 1 ! Is it monochrome?
919 jz got_video
920 inc ax
921 jmp got_video
922
923no_ega: int 0x11 ! Get bit pattern for equipment
924 and ax, 0x30 ! Isolate color/mono field
925 sub ax, 0x30
926 jz got_video ! Is it an MDA?
927 mov ax, 1 ! No it's CGA
928
929got_video:
930 ret
931
932
933! Function to leave the boot monitor and run Minix.
934.define _minix
935
936! void minix(u32_t koff, u32_t kcs, u32_t kds,
937! char *bootparams, size_t paramsize, u32_t aout);
938_minix:
939 push bp
940 mov bp, sp ! Pointer to arguments
941
942 mov dx, 0x03F2 ! Floppy motor drive control bits
943 movb al, 0x0C ! Bits 4-7 for floppy 0-3 are off
944 outb dx ! Kill the motors
945 push ds
946 xor ax, ax ! Vector & BIOS data segments
947 mov ds, ax
948 andb (0x043F), 0xF0 ! Clear diskette motor status bits of BIOS
949 pop ds
950 cli ! No more interruptions
951
952 test (_k_flags), K_I386 ! Minix-386?
953 jnz minix386
954
955! Call Minix in real mode.
956minix86:
957 push 22(bp) ! Address of a.out headers
958 push 20(bp)
959
960 push 18(bp) ! # bytes of boot parameters
961 push 16(bp) ! Address of boot parameters
962
963 mov dx, cs ! Monitor far return address
964 mov ax, ret86
965 cmp (_mem+14), 0 ! Any extended memory? (mem[1].size > 0 ?)
966 jnz 0f
967 xor dx, dx ! If no ext mem then monitor not preserved
968 xor ax, ax
9690: push dx ! Push monitor far return address or zero
970 push ax
971
972 mov ax, 8(bp)
973 mov dx, 10(bp)
974 call abs2seg
975 push dx ! Kernel code segment
976 push 4(bp) ! Kernel code offset
977 mov ax, 12(bp)
978 mov dx, 14(bp)
979 call abs2seg
980 mov ds, dx ! Kernel data segment
981 mov es, dx ! Set es to kernel data too
982 retf ! Make a far call to the kernel
983
984! Call 386 Minix in 386 mode.
985minix386:
986 cseg mov (cs_real-2), cs ! Patch CS and DS into the instructions that
987 cseg mov (ds_real-2), ds ! reload them when switching back to real mode
988 mov eax, cr0
989 orb al, 0x01 ! Set PE (protection enable) bit
990 o32 mov (msw), eax ! Save as protected mode machine status word
991
992 mov dx, ds ! Monitor ds
993 mov ax, p_gdt ! dx:ax = Global descriptor table
994 call seg2abs
995 mov (p_gdt_desc+2), ax
996 movb (p_gdt_desc+4), dl ! Set base of global descriptor table
997
998 mov ax, 12(bp)
999 mov dx, 14(bp) ! Kernel ds (absolute address)
1000 mov (p_ds_desc+2), ax
1001 movb (p_ds_desc+4), dl ! Set base of kernel data segment
1002
1003 mov dx, ss ! Monitor ss
1004 xor ax, ax ! dx:ax = Monitor stack segment
1005 call seg2abs ! Minix starts with the stack of the monitor
1006 mov (p_ss_desc+2), ax
1007 movb (p_ss_desc+4), dl
1008
1009 mov ax, 8(bp)
1010 mov dx, 10(bp) ! Kernel cs (absolute address)
1011 mov (p_cs_desc+2), ax
1012 movb (p_cs_desc+4), dl
1013
1014 mov dx, cs ! Monitor cs
1015 xor ax, ax ! dx:ax = Monitor code segment
1016 call seg2abs
1017 mov (p_mcs_desc+2), ax
1018 movb (p_mcs_desc+4), dl
1019
1020 push MCS_SELECTOR
1021 push int86 ! Far address to INT86 support
1022
1023 o32 push 20(bp) ! Address of a.out headers
1024
1025 push 0
1026 push 18(bp) ! 32 bit size of parameters on stack
1027 push 0
1028 push 16(bp) ! 32 bit address of parameters (ss relative)
1029
1030 push MCS_SELECTOR
1031 push ret386 ! Monitor far return address
1032
1033 push 0
1034 push CS_SELECTOR
1035 push 6(bp)
1036 push 4(bp) ! 32 bit far address to kernel entry point
1037
1038 call real2prot ! Switch to protected mode
1039 mov ax, DS_SELECTOR
1040 mov ds, ax ! Kernel data
1041 mov ax, ES_SELECTOR
1042 mov es, ax ! Flat 4 Gb
1043 o32 retf ! Make a far call to the kernel
1044
1045! Minix-86 returns here on a halt or reboot.
1046ret86:
1047 mov 8(bp), ax
1048 mov 10(bp), dx ! Return value
1049 jmp return
1050
1051! Minix-386 returns here on a halt or reboot.
1052ret386:
1053 o32 mov 8(bp), eax ! Return value
1054 call prot2real ! Switch to real mode
1055
1056return:
1057 mov sp, bp ! Pop parameters
1058 sti ! Can take interrupts again
1059
1060 call _get_video ! MDA, CGA, EGA, ...
1061 movb dh, 24 ! dh = row 24
1062 cmp ax, 2 ! At least EGA?
1063 jb is25 ! Otherwise 25 rows
1064 push ds
1065 xor ax, ax ! Vector & BIOS data segments
1066 mov ds, ax
1067 movb dh, (0x0484) ! Number of rows on display minus one
1068 pop ds
1069is25:
1070 xorb dl, dl ! dl = column 0
1071 xorb bh, bh ! Page 0
1072 movb ah, 0x02 ! Set cursor position
1073 int 0x10
1074
1075 xorb ah, ah ! Whack the disk system, Minix may have messed
1076 movb dl, 0x80 ! it up
1077 int 0x13
1078
1079 call gettrueproc
1080 cmp ax, 286
1081 jb noclock
1082 xorb al, al
1083tryclk: decb al
1084 jz noclock
1085 movb ah, 0x02 ! Get real-time clock time (from CMOS clock)
1086 int 0x1A
1087 jc tryclk ! Carry set, not running or being updated
1088 movb al, ch ! ch = hour in BCD
1089 call bcd ! al = (al >> 4) * 10 + (al & 0x0F)
1090 mulb (c60) ! 60 minutes in an hour
1091 mov bx, ax ! bx = hour * 60
1092 movb al, cl ! cl = minutes in BCD
1093 call bcd
1094 add bx, ax ! bx = hour * 60 + minutes
1095 movb al, dh ! dh = seconds in BCD
1096 call bcd
1097 xchg ax, bx ! ax = hour * 60 + minutes, bx = seconds
1098 mul (c60) ! dx-ax = (hour * 60 + minutes) * 60
1099 add bx, ax
1100 adc dx, 0 ! dx-bx = seconds since midnight
1101 mov ax, dx
1102 mul (c19663)
1103 xchg ax, bx
1104 mul (c19663)
1105 add dx, bx ! dx-ax = dx-bx * (0x1800B0 / (2*2*2*2*5))
1106 mov cx, ax ! (0x1800B0 = ticks per day of BIOS clock)
1107 mov ax, dx
1108 xor dx, dx
1109 div (c1080)
1110 xchg ax, cx
1111 div (c1080) ! cx-ax = dx-ax / (24*60*60 / (2*2*2*2*5))
1112 mov dx, ax ! cx-dx = ticks since midnight
1113 movb ah, 0x01 ! Set system time
1114 int 0x1A
1115noclock:
1116
1117 mov ax, 8(bp)
1118 mov dx, 10(bp) ! dx-ax = return value from the kernel
1119 pop bp
1120 ret ! Return to monitor as if nothing much happened
1121
1122! Transform BCD number in al to a regular value in ax.
1123bcd: movb ah, al
1124 shrb ah, 4
1125 andb al, 0x0F
1126 aad ! ax = (al >> 4) * 10 + (al & 0x0F)
1127 ret
1128
1129! Support function for Minix-386 to make an 8086 interrupt call.
1130int86:
1131 mov bp, sp
1132 call prot2real
1133
1134 o32 xor eax, eax
1135 mov es, ax ! Vector & BIOS data segments
1136o32 eseg mov (0x046C), eax ! Clear BIOS clock tick counter
1137
1138 sti ! Enable interrupts
1139
1140 movb al, 0xCD ! INT instruction
1141 movb ah, 8(bp) ! Interrupt number?
1142 testb ah, ah
1143 jnz 0f ! Nonzero if INT, otherwise far call
1144 push cs
1145 push intret+2 ! Far return address
1146 o32 push 12(bp) ! Far driver address
1147 mov ax, 0x90CB ! RETF; NOP
11480: cseg mov (intret), ax ! Patch 'INT n' or 'RETF; NOP' into code
1149
1150 mov ds, 16(bp) ! Load parameters
1151 mov es, 18(bp)
1152 o32 mov eax, 20(bp)
1153 o32 mov ebx, 24(bp)
1154 o32 mov ecx, 28(bp)
1155 o32 mov edx, 32(bp)
1156 o32 mov esi, 36(bp)
1157 o32 mov edi, 40(bp)
1158 o32 mov ebp, 44(bp)
1159
1160intret: int 0xFF ! Do the interrupt or far call
1161
1162 o32 push ebp ! Save results
1163 o32 pushf
1164 mov bp, sp
1165 o32 pop 8+8(bp) ! eflags
1166 mov 8+16(bp), ds
1167 mov 8+18(bp), es
1168 o32 mov 8+20(bp), eax
1169 o32 mov 8+24(bp), ebx
1170 o32 mov 8+28(bp), ecx
1171 o32 mov 8+32(bp), edx
1172 o32 mov 8+36(bp), esi
1173 o32 mov 8+40(bp), edi
1174 o32 pop 8+44(bp) ! ebp
1175
1176 cli ! Disable interrupts
1177
1178 xor ax, ax
1179 mov ds, ax ! Vector & BIOS data segments
1180 o32 mov cx, (0x046C) ! Collect lost clock ticks in ecx
1181
1182 mov ax, ss
1183 mov ds, ax ! Restore monitor ds
1184 call real2prot
1185 mov ax, DS_SELECTOR ! Kernel data
1186 mov ds, ax
1187 o32 retf ! Return to the kernel
1188
1189! Switch from real to protected mode.
1190real2prot:
1191 movb ah, 0x02 ! Code for A20 enable
1192 call gate_A20
1193
1194 lgdt (p_gdt_desc) ! Global descriptor table
1195 o32 mov eax, (pdbr) ! Load page directory base register
1196 mov cr3, eax
1197 mov eax, cr0
1198 o32 xchg eax, (msw) ! Exchange real mode msw for protected mode msw
1199 mov cr0, eax
1200 jmpf MCS_SELECTOR:cs_prot ! Set code segment selector
1201cs_prot:
1202 mov ax, SS_SELECTOR ! Set data selectors
1203 mov ds, ax
1204 mov es, ax
1205 mov ss, ax
1206 ret
1207
1208! Switch from protected to real mode.
1209prot2real:
1210 lidt (p_idt_desc) ! Real mode interrupt vectors
1211 mov eax, cr3
1212 o32 mov (pdbr), eax ! Save page directory base register
1213 mov eax, cr0
1214 o32 xchg eax, (msw) ! Exchange protected mode msw for real mode msw
1215 mov cr0, eax
1216 jmpf 0xDEAD:cs_real ! Reload cs register
1217cs_real:
1218 mov ax, 0xBEEF
1219ds_real:
1220 mov ds, ax ! Reload data segment registers
1221 mov es, ax
1222 mov ss, ax
1223
1224 xorb ah, ah ! Code for A20 disable
1225 !jmp gate_A20
1226
1227! Enable (ah = 0x02) or disable (ah = 0x00) the A20 address line.
1228gate_A20:
1229 cmp (bus), 2 ! PS/2 bus?
1230 je gate_PS_A20
1231 call kb_wait
1232 movb al, 0xD1 ! Tell keyboard that a command is coming
1233 outb 0x64
1234 call kb_wait
1235 movb al, 0xDD ! 0xDD = A20 disable code if ah = 0x00
1236 orb al, ah ! 0xDF = A20 enable code if ah = 0x02
1237 outb 0x60
1238 call kb_wait
1239 movb al, 0xFF ! Pulse output port
1240 outb 0x64
1241 call kb_wait ! Wait for the A20 line to settle down
1242 ret
1243kb_wait:
1244 inb 0x64
1245 testb al, 0x02 ! Keyboard input buffer full?
1246 jnz kb_wait ! If so, wait
1247 ret
1248
1249gate_PS_A20: ! The PS/2 can twiddle A20 using port A
1250 inb 0x92 ! Read port A
1251 andb al, 0xFD
1252 orb al, ah ! Set A20 bit to the required state
1253 outb 0x92 ! Write port A
1254 jmp .+2 ! Small delay
1255A20ok: inb 0x92 ! Check port A
1256 andb al, 0x02
1257 cmpb al, ah ! A20 line settled down to the new state?
1258 jne A20ok ! If not then wait
1259 ret
1260
1261! void int15(bios_env_t *ep)
1262! Do an "INT 15" call, primarily for APM (Power Management).
1263.define _int15
1264_int15:
1265 push si ! Save callee-save register si
1266 mov si, sp
1267 mov si, 4(si) ! ep
1268 mov ax, (si) ! ep->ax
1269 mov bx, 2(si) ! ep->bx
1270 mov cx, 4(si) ! ep->cx
1271 int 0x15 ! INT 0x15 BIOS call
1272 pushf ! Save flags
1273 mov (si), ax ! ep->ax
1274 mov 2(si), bx ! ep->bx
1275 mov 4(si), cx ! ep->cx
1276 pop 6(si) ! ep->flags
1277 pop si ! Restore
1278 ret
1279
1280.sect .rom
1281 .align 4
1282c60: .data2 60 ! Constants for MUL and DIV
1283c1024: .data2 1024
1284c1080: .data2 1080
1285c19663: .data2 19663
1286
1287.sect .data
1288 .align 4
1289
1290! Global descriptor tables.
1291 UNSET = 0 ! Must be computed
1292
1293! For "Extended Memory Block Move".
1294x_gdt:
1295x_null_desc:
1296 ! Null descriptor
1297 .data2 0x0000, 0x0000
1298 .data1 0x00, 0x00, 0x00, 0x00
1299x_gdt_desc:
1300 ! Descriptor for this descriptor table
1301 .data2 6*8-1, UNSET
1302 .data1 UNSET, 0x00, 0x00, 0x00
1303x_src_desc:
1304 ! Source segment descriptor
1305 .data2 0xFFFF, UNSET
1306 .data1 UNSET, 0x92, 0x00, 0x00
1307x_dst_desc:
1308 ! Destination segment descriptor
1309 .data2 0xFFFF, UNSET
1310 .data1 UNSET, 0x92, 0x00, 0x00
1311x_bios_desc:
1312 ! BIOS segment descriptor (scratch for int 0x15)
1313 .data2 UNSET, UNSET
1314 .data1 UNSET, UNSET, UNSET, UNSET
1315x_ss_desc:
1316 ! BIOS stack segment descriptor (scratch for int 0x15)
1317 .data2 UNSET, UNSET
1318 .data1 UNSET, UNSET, UNSET, UNSET
1319
1320! Protected mode descriptor table.
1321p_gdt:
1322p_null_desc:
1323 ! Null descriptor
1324 .data2 0x0000, 0x0000
1325 .data1 0x00, 0x00, 0x00, 0x00
1326p_gdt_desc:
1327 ! Descriptor for this descriptor table
1328 .data2 8*8-1, UNSET
1329 .data1 UNSET, 0x00, 0x00, 0x00
1330p_idt_desc:
1331 ! Real mode interrupt descriptor table descriptor
1332 .data2 0x03FF, 0x0000
1333 .data1 0x00, 0x00, 0x00, 0x00
1334p_ds_desc:
1335 ! Kernel data segment descriptor (4Gb flat)
1336 .data2 0xFFFF, UNSET
1337 .data1 UNSET, 0x92, 0xCF, 0x00
1338p_es_desc:
1339 ! Physical memory descriptor (4Gb flat)
1340 .data2 0xFFFF, 0x0000
1341 .data1 0x00, 0x92, 0xCF, 0x00
1342p_ss_desc:
1343 ! Monitor data segment descriptor (64Kb flat)
1344 .data2 0xFFFF, UNSET
1345 .data1 UNSET, 0x92, 0x00, 0x00
1346p_cs_desc:
1347 ! Kernel code segment descriptor (4Gb flat)
1348 .data2 0xFFFF, UNSET
1349 .data1 UNSET, 0x9A, 0xCF, 0x00
1350p_mcs_desc:
1351 ! Monitor code segment descriptor (64 kb flat) (unused)
1352 .data2 0xFFFF, UNSET
1353 .data1 UNSET, 0x9A, 0x00, 0x00
1354
1355xms_handle: .data2 -1 ! Handle of allocated XMS block
1356vfd: .data2 -1 ! Virtual disk file handle
1357
1358.sect .bss
1359 .comm xms_driver, 4 ! Vector to XMS driver
1360 .comm old_vid_mode, 2 ! Video mode at startup
1361 .comm cur_vid_mode, 2 ! Current video mode
1362 .comm msw, 4 ! Saved machine status word (cr0)
1363 .comm pdbr, 4 ! Saved page directory base register (cr3)
1364 .comm escape, 2 ! Escape typed?
1365 .comm bus, 2 ! Saved return value of _get_bus
1366 .comm unchar, 2 ! Char returned by ungetch(c)
1367
1368!
1369! $PchId: doshead.ack.s,v 1.7 2002/02/27 19:37:52 philip Exp $
Note: See TracBrowser for help on using the repository browser.