1 | ! Boothead.s - 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 | ! The primary bootstrap code supplies the following parameters in registers:
|
---|
9 | ! dl = Boot-device.
|
---|
10 | ! es:si = Partition table entry if hard disk.
|
---|
11 | !
|
---|
12 | .text
|
---|
13 |
|
---|
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
|
---|
20 | a_text = 8
|
---|
21 | a_data = 12
|
---|
22 | a_bss = 16
|
---|
23 | a_total = 24
|
---|
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
|
---|
29 |
|
---|
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
|
---|
35 |
|
---|
36 | ESC = 0x1B ! Escape character
|
---|
37 |
|
---|
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 |
|
---|
45 | .text
|
---|
46 |
|
---|
47 | ! Set segment registers and stack pointer using the programs own header!
|
---|
48 | ! The header is either 32 bytes (short form) or 48 bytes (long form). The
|
---|
49 | ! bootblock will jump to address 0x10030 in both cases, calling one of the
|
---|
50 | ! two jmpf instructions below.
|
---|
51 |
|
---|
52 | jmpf boot, LOADSEG+3 ! Set cs right (skipping long a.out header)
|
---|
53 | .space 11 ! jmpf + 11 = 16 bytes
|
---|
54 | jmpf boot, LOADSEG+2 ! Set cs right (skipping short a.out header)
|
---|
55 | boot:
|
---|
56 | mov ax, #LOADSEG
|
---|
57 | mov ds, ax ! ds = header
|
---|
58 |
|
---|
59 | movb al, a_flags
|
---|
60 | testb al, #A_SEP ! Separate I&D?
|
---|
61 | jnz sepID
|
---|
62 | comID: xor ax, ax
|
---|
63 | xchg ax, a_text ! No text
|
---|
64 | add a_data, ax ! Treat all text as data
|
---|
65 | sepID:
|
---|
66 | mov ax, a_total ! Total nontext memory usage
|
---|
67 | and ax, #0xFFFE ! Round down to even
|
---|
68 | mov a_total, ax ! total - text = data + bss + heap + stack
|
---|
69 | cli ! Ignore interrupts while stack in limbo
|
---|
70 | mov sp, ax ! Set sp at the top of all that
|
---|
71 |
|
---|
72 | mov ax, a_text ! Determine offset of ds above cs
|
---|
73 | movb cl, #4
|
---|
74 | shr ax, cl
|
---|
75 | mov cx, cs
|
---|
76 | add ax, cx
|
---|
77 | mov ds, ax ! ds = cs + text / 16
|
---|
78 | mov ss, ax
|
---|
79 | sti ! Stack ok now
|
---|
80 | push es ! Save es, we need it for the partition table
|
---|
81 | mov es, ax
|
---|
82 | cld ! C compiler wants UP
|
---|
83 |
|
---|
84 | ! Clear bss
|
---|
85 | xor ax, ax ! Zero
|
---|
86 | mov di, #_edata ! Start of bss is at end of data
|
---|
87 | mov cx, #_end ! End of bss (begin of heap)
|
---|
88 | sub cx, di ! Number of bss bytes
|
---|
89 | shr cx, #1 ! Number of words
|
---|
90 | rep
|
---|
91 | stos ! Clear bss
|
---|
92 |
|
---|
93 | ! Copy primary boot parameters to variables. (Can do this now that bss is
|
---|
94 | ! cleared and may be written into).
|
---|
95 | xorb dh, dh
|
---|
96 | mov _device, dx ! Boot device (probably 0x00 or 0x80)
|
---|
97 | mov _rem_part+0, si ! Remote partition table offset
|
---|
98 | pop _rem_part+2 ! and segment (saved es)
|
---|
99 |
|
---|
100 | ! Remember the current video mode for restoration on exit.
|
---|
101 | movb ah, #0x0F ! Get current video mode
|
---|
102 | int 0x10
|
---|
103 | andb al, #0x7F ! Mask off bit 7 (no blanking)
|
---|
104 | movb old_vid_mode, al
|
---|
105 | movb cur_vid_mode, al
|
---|
106 |
|
---|
107 | ! Give C code access to the code segment, data segment and the size of this
|
---|
108 | ! process.
|
---|
109 | xor ax, ax
|
---|
110 | mov dx, cs
|
---|
111 | call seg2abs
|
---|
112 | mov _caddr+0, ax
|
---|
113 | mov _caddr+2, dx
|
---|
114 | xor ax, ax
|
---|
115 | mov dx, ds
|
---|
116 | call seg2abs
|
---|
117 | mov _daddr+0, ax
|
---|
118 | mov _daddr+2, dx
|
---|
119 | push ds
|
---|
120 | mov ax, #LOADSEG
|
---|
121 | mov ds, ax ! Back to the header once more
|
---|
122 | mov ax, a_total+0
|
---|
123 | mov dx, a_total+2 ! dx:ax = data + bss + heap + stack
|
---|
124 | add ax, a_text+0
|
---|
125 | adc dx, a_text+2 ! dx:ax = text + data + bss + heap + stack
|
---|
126 | pop ds
|
---|
127 | mov _runsize+0, ax
|
---|
128 | mov _runsize+2, dx ! 32 bit size of this process
|
---|
129 |
|
---|
130 | ! Determine available memory as a list of (base,size) pairs as follows:
|
---|
131 | ! mem[0] = low memory, mem[1] = memory between 1M and 16M, mem[2] = memory
|
---|
132 | ! above 16M. Last two coalesced into mem[1] if adjacent.
|
---|
133 | mov di, #_mem ! di = memory list
|
---|
134 | int 0x12 ! Returns low memory size (in K) in ax
|
---|
135 | mul c1024
|
---|
136 | mov 4(di), ax ! mem[0].size = low memory size in bytes
|
---|
137 | mov 6(di), dx
|
---|
138 | call _getprocessor
|
---|
139 | cmp ax, #286 ! Only 286s and above have extended memory
|
---|
140 | jb no_ext
|
---|
141 | cmp ax, #486 ! Assume 486s were the first to have >64M
|
---|
142 | jb small_ext ! (It helps to be paranoid when using the BIOS)
|
---|
143 | big_ext:
|
---|
144 | mov ax, #0xE801 ! Code for get memory size for >64M
|
---|
145 | int 0x15 ! ax = mem at 1M per 1K, bx = mem at 16M per 64K
|
---|
146 | jnc got_ext
|
---|
147 | small_ext:
|
---|
148 | movb ah, #0x88 ! Code for get extended memory size
|
---|
149 | clc ! Carry will stay clear if call exists
|
---|
150 | int 0x15 ! Returns size (in K) in ax for AT's
|
---|
151 | jc no_ext
|
---|
152 | test ax, ax ! An AT with no extended memory?
|
---|
153 | jz no_ext
|
---|
154 | xor bx, bx ! bx = mem above 16M per 64K = 0
|
---|
155 | got_ext:
|
---|
156 | mov cx, ax ! cx = copy of ext mem at 1M
|
---|
157 | mov 10(di), #0x0010 ! mem[1].base = 0x00100000 (1M)
|
---|
158 | mul c1024
|
---|
159 | mov 12(di), ax ! mem[1].size = "ext mem at 1M" * 1024
|
---|
160 | mov 14(di), dx
|
---|
161 | test bx, bx
|
---|
162 | jz no_ext ! No more ext mem above 16M?
|
---|
163 | cmp cx, #15*1024 ! Chunks adjacent? (precisely 15M at 1M?)
|
---|
164 | je adj_ext
|
---|
165 | mov 18(di), #0x0100 ! mem[2].base = 0x01000000 (16M)
|
---|
166 | mov 22(di), bx ! mem[2].size = "ext mem at 16M" * 64K
|
---|
167 | jmp no_ext
|
---|
168 | adj_ext:
|
---|
169 | add 14(di), bx ! Add ext mem above 16M to mem below 16M
|
---|
170 | no_ext:
|
---|
171 |
|
---|
172 |
|
---|
173 | ! Time to switch to a higher level language (not much higher)
|
---|
174 | call _boot
|
---|
175 |
|
---|
176 | ! void ..exit(int status)
|
---|
177 | ! Exit the monitor by rebooting the system.
|
---|
178 | .define _exit, __exit, ___exit ! Make various compilers happy
|
---|
179 | _exit:
|
---|
180 | __exit:
|
---|
181 | ___exit:
|
---|
182 | mov bx, sp
|
---|
183 | cmp 2(bx), #0 ! Good exit status?
|
---|
184 | jz reboot
|
---|
185 | quit: mov ax, #any_key
|
---|
186 | push ax
|
---|
187 | call _printf
|
---|
188 | xorb ah, ah ! Read character from keyboard
|
---|
189 | int 0x16
|
---|
190 | reboot: call dev_reset
|
---|
191 | call restore_video
|
---|
192 | int 0x19 ! Reboot the system
|
---|
193 | .data
|
---|
194 | any_key:
|
---|
195 | .ascii "\nHit any key to reboot\n\0"
|
---|
196 | .text
|
---|
197 |
|
---|
198 | ! u32_t mon2abs(void *ptr)
|
---|
199 | ! Address in monitor data to absolute address.
|
---|
200 | .define _mon2abs
|
---|
201 | _mon2abs:
|
---|
202 | mov bx, sp
|
---|
203 | mov ax, 2(bx) ! ptr
|
---|
204 | mov dx, ds ! Monitor data segment
|
---|
205 | jmp seg2abs
|
---|
206 |
|
---|
207 | ! u32_t vec2abs(vector *vec)
|
---|
208 | ! 8086 interrupt vector to absolute address.
|
---|
209 | .define _vec2abs
|
---|
210 | _vec2abs:
|
---|
211 | mov bx, sp
|
---|
212 | mov bx, 2(bx)
|
---|
213 | mov ax, (bx)
|
---|
214 | mov dx, 2(bx) ! dx:ax vector
|
---|
215 | !jmp seg2abs ! Translate
|
---|
216 |
|
---|
217 | seg2abs: ! Translate dx:ax to the 32 bit address dx-ax
|
---|
218 | push cx
|
---|
219 | movb ch, dh
|
---|
220 | movb cl, #4
|
---|
221 | shl dx, cl
|
---|
222 | shrb ch, cl ! ch-dx = dx << 4
|
---|
223 | add ax, dx
|
---|
224 | adcb ch, #0 ! ch-ax = ch-dx + ax
|
---|
225 | movb dl, ch
|
---|
226 | xorb dh, dh ! dx-ax = ch-ax
|
---|
227 | pop cx
|
---|
228 | ret
|
---|
229 |
|
---|
230 | abs2seg: ! Translate the 32 bit address dx-ax to dx:ax
|
---|
231 | push cx
|
---|
232 | movb ch, dl
|
---|
233 | mov dx, ax ! ch-dx = dx-ax
|
---|
234 | and ax, #0x000F ! Offset in ax
|
---|
235 | movb cl, #4
|
---|
236 | shr dx, cl
|
---|
237 | shlb ch, cl
|
---|
238 | orb dh, ch ! dx = ch-dx >> 4
|
---|
239 | pop cx
|
---|
240 | ret
|
---|
241 |
|
---|
242 | ! void raw_copy(u32_t dstaddr, u32_t srcaddr, u32_t count)
|
---|
243 | ! Copy count bytes from srcaddr to dstaddr. Don't do overlaps.
|
---|
244 | ! Also handles copying words to or from extended memory.
|
---|
245 | .define _raw_copy
|
---|
246 | _raw_copy:
|
---|
247 | push bp
|
---|
248 | mov bp, sp
|
---|
249 | push si
|
---|
250 | push di ! Save C variable registers
|
---|
251 | copy:
|
---|
252 | cmp 14(bp), #0
|
---|
253 | jnz bigcopy
|
---|
254 | mov cx, 12(bp)
|
---|
255 | jcxz copydone ! Count is zero, end copy
|
---|
256 | cmp cx, #0xFFF0
|
---|
257 | jb smallcopy
|
---|
258 | bigcopy:mov cx, #0xFFF0 ! Don't copy more than about 64K at once
|
---|
259 | smallcopy:
|
---|
260 | push cx ! Save copying count
|
---|
261 | mov ax, 4(bp)
|
---|
262 | mov dx, 6(bp)
|
---|
263 | cmp dx, #0x0010 ! Copy to extended memory?
|
---|
264 | jae ext_copy
|
---|
265 | cmp 10(bp), #0x0010 ! Copy from extended memory?
|
---|
266 | jae ext_copy
|
---|
267 | call abs2seg
|
---|
268 | mov di, ax
|
---|
269 | mov es, dx ! es:di = dstaddr
|
---|
270 | mov ax, 8(bp)
|
---|
271 | mov dx, 10(bp)
|
---|
272 | call abs2seg
|
---|
273 | mov si, ax
|
---|
274 | mov ds, dx ! ds:si = srcaddr
|
---|
275 | shr cx, #1 ! Words to move
|
---|
276 | rep
|
---|
277 | movs ! Do the word copy
|
---|
278 | adc cx, cx ! One more byte?
|
---|
279 | rep
|
---|
280 | movsb ! Do the byte copy
|
---|
281 | mov ax, ss ! Restore ds and es from the remaining ss
|
---|
282 | mov ds, ax
|
---|
283 | mov es, ax
|
---|
284 | jmp copyadjust
|
---|
285 | ext_copy:
|
---|
286 | mov x_dst_desc+2, ax
|
---|
287 | movb x_dst_desc+4, dl ! Set base of destination segment
|
---|
288 | mov ax, 8(bp)
|
---|
289 | mov dx, 10(bp)
|
---|
290 | mov x_src_desc+2, ax
|
---|
291 | movb x_src_desc+4, dl ! Set base of source segment
|
---|
292 | mov si, #x_gdt ! es:si = global descriptor table
|
---|
293 | shr cx, #1 ! Words to move
|
---|
294 | movb ah, #0x87 ! Code for extended memory move
|
---|
295 | int 0x15
|
---|
296 | copyadjust:
|
---|
297 | pop cx ! Restore count
|
---|
298 | add 4(bp), cx
|
---|
299 | adc 6(bp), #0 ! srcaddr += copycount
|
---|
300 | add 8(bp), cx
|
---|
301 | adc 10(bp), #0 ! dstaddr += copycount
|
---|
302 | sub 12(bp), cx
|
---|
303 | sbb 14(bp), #0 ! count -= copycount
|
---|
304 | jmp copy ! and repeat
|
---|
305 | copydone:
|
---|
306 | pop di
|
---|
307 | pop si ! Restore C variable registers
|
---|
308 | pop bp
|
---|
309 | ret
|
---|
310 |
|
---|
311 | ! u16_t get_word(u32_t addr);
|
---|
312 | ! void put_word(u32_t addr, u16_t word);
|
---|
313 | ! Read or write a 16 bits word at an arbitrary location.
|
---|
314 | .define _get_word, _put_word
|
---|
315 | _get_word:
|
---|
316 | mov bx, sp
|
---|
317 | call gp_getaddr
|
---|
318 | mov ax, (bx) ! Word to get from addr
|
---|
319 | jmp gp_ret
|
---|
320 | _put_word:
|
---|
321 | mov bx, sp
|
---|
322 | push 6(bx) ! Word to store at addr
|
---|
323 | call gp_getaddr
|
---|
324 | pop (bx) ! Store the word
|
---|
325 | jmp gp_ret
|
---|
326 | gp_getaddr:
|
---|
327 | mov ax, 2(bx)
|
---|
328 | mov dx, 4(bx)
|
---|
329 | call abs2seg
|
---|
330 | mov bx, ax
|
---|
331 | mov ds, dx ! ds:bx = addr
|
---|
332 | ret
|
---|
333 | gp_ret:
|
---|
334 | push es
|
---|
335 | pop ds ! Restore ds
|
---|
336 | ret
|
---|
337 |
|
---|
338 | ! void relocate(void);
|
---|
339 | ! After the program has copied itself to a safer place, it needs to change
|
---|
340 | ! the segment registers. Caddr has already been set to the new location.
|
---|
341 | .define _relocate
|
---|
342 | _relocate:
|
---|
343 | pop bx ! Return address
|
---|
344 | mov ax, _caddr+0
|
---|
345 | mov dx, _caddr+2
|
---|
346 | call abs2seg
|
---|
347 | mov cx, dx ! cx = new code segment
|
---|
348 | mov ax, cs ! Old code segment
|
---|
349 | sub ax, cx ! ax = -(new - old) = -Moving offset
|
---|
350 | mov dx, ds
|
---|
351 | sub dx, ax
|
---|
352 | mov ds, dx ! ds += (new - old)
|
---|
353 | mov es, dx
|
---|
354 | mov ss, dx
|
---|
355 | xor ax, ax
|
---|
356 | call seg2abs
|
---|
357 | mov _daddr+0, ax
|
---|
358 | mov _daddr+2, dx ! New data address
|
---|
359 | push cx ! New text segment
|
---|
360 | push bx ! Return offset of this function
|
---|
361 | retf ! Relocate
|
---|
362 |
|
---|
363 | ! void *brk(void *addr)
|
---|
364 | ! void *sbrk(size_t incr)
|
---|
365 | ! Cannot fail implementations of brk(2) and sbrk(3), so we can use
|
---|
366 | ! malloc(3). They reboot on stack collision instead of returning -1.
|
---|
367 | .data
|
---|
368 | .align 2
|
---|
369 | break: .data2 _end ! A fake heap pointer
|
---|
370 | .text
|
---|
371 | .define _brk, __brk, _sbrk, __sbrk
|
---|
372 | _brk:
|
---|
373 | __brk: ! __brk is for the standard C compiler
|
---|
374 | xor ax, ax
|
---|
375 | jmp sbrk ! break= 0; return sbrk(addr);
|
---|
376 | _sbrk:
|
---|
377 | __sbrk:
|
---|
378 | mov ax, break ! ax= current break
|
---|
379 | sbrk: push ax ! save it as future return value
|
---|
380 | mov bx, sp ! Stack is now: (retval, retaddr, incr, ...)
|
---|
381 | add ax, 4(bx) ! ax= break + increment
|
---|
382 | mov break, ax ! Set new break
|
---|
383 | lea dx, -1024(bx) ! sp minus a bit of breathing space
|
---|
384 | cmp dx, ax ! Compare with the new break
|
---|
385 | jb heaperr ! Suffocating noises
|
---|
386 | lea dx, -4096(bx) ! A warning when heap+stack goes < 4K
|
---|
387 | cmp dx, ax
|
---|
388 | jae plenty ! No reason to complain
|
---|
389 | mov ax, #memwarn
|
---|
390 | push ax
|
---|
391 | call _printf ! Warn about memory running low
|
---|
392 | pop ax
|
---|
393 | movb memwarn, #0 ! No more warnings
|
---|
394 | plenty: pop ax ! Return old break (0 for brk)
|
---|
395 | ret
|
---|
396 | heaperr:mov ax, #chmem
|
---|
397 | push ax
|
---|
398 | mov ax, #nomem
|
---|
399 | push ax
|
---|
400 | call _printf
|
---|
401 | jmp quit
|
---|
402 | .data
|
---|
403 | nomem: .ascii "\nOut of%s\0"
|
---|
404 | memwarn:.ascii "\nLow on"
|
---|
405 | chmem: .ascii " memory, use chmem to increase the heap\n\0"
|
---|
406 | .text
|
---|
407 |
|
---|
408 | ! int dev_open(void);
|
---|
409 | ! Given the device "_device" figure out if it exists and what its number
|
---|
410 | ! of heads and sectors may be. Return the BIOS error code on error,
|
---|
411 | ! otherwise 0.
|
---|
412 | .define _dev_open
|
---|
413 | _dev_open:
|
---|
414 | call dev_reset ! Optionally reset the disks
|
---|
415 | movb dev_state, #0 ! State is "closed"
|
---|
416 | push es
|
---|
417 | push di ! Save registers used by BIOS calls
|
---|
418 | movb dl, _device ! The default device
|
---|
419 | cmpb dl, #0x80 ! Floppy < 0x80, winchester >= 0x80
|
---|
420 | jae winchester
|
---|
421 | floppy:
|
---|
422 | mov di, #3 ! Three tries to init drive by reading sector 0
|
---|
423 | finit0: xor ax, ax
|
---|
424 | mov es, ax
|
---|
425 | mov bx, #BUFFER ! es:bx = scratch buffer
|
---|
426 | mov ax, #0x0201 ! Read sector, #sectors = 1
|
---|
427 | mov cx, #0x0001 ! Track 0, first sector
|
---|
428 | xorb dh, dh ! Drive dl, head 0
|
---|
429 | int 0x13
|
---|
430 | jnc finit0ok ! Sector 0 read ok?
|
---|
431 | cmpb ah, #0x80 ! Disk timed out? (Floppy drive empty)
|
---|
432 | je geoerr
|
---|
433 | dec di
|
---|
434 | jz geoerr
|
---|
435 | xorb ah, ah ! Reset drive
|
---|
436 | int 0x13
|
---|
437 | jc geoerr
|
---|
438 | jmp finit0 ! Retry once more, it may need to spin up
|
---|
439 | finit0ok:
|
---|
440 | mov di, #seclist ! List of per floppy type sectors/track
|
---|
441 | flast: movb cl, (di) ! Sectors per track to test
|
---|
442 | cmpb cl, #9 ! No need to do the last 720K/360K test
|
---|
443 | je ftestok
|
---|
444 | xor ax, ax
|
---|
445 | mov es, ax
|
---|
446 | mov bx, #BUFFER ! es:bx = scratch buffer
|
---|
447 | mov ax, #0x0201 ! Read sector, #sectors = 1
|
---|
448 | xorb ch, ch ! Track 0, last sector
|
---|
449 | xorb dh, dh ! Drive dl, head 0
|
---|
450 | int 0x13
|
---|
451 | jnc ftestok ! Sector cl read ok?
|
---|
452 | xorb ah, ah ! Reset drive
|
---|
453 | int 0x13
|
---|
454 | jc geoerr
|
---|
455 | inc di ! Try next sec/track number
|
---|
456 | jmp flast
|
---|
457 | ftestok:
|
---|
458 | movb dh, #2 ! Floppies have two sides
|
---|
459 | jmp geoboth
|
---|
460 | winchester:
|
---|
461 | movb ah, #0x08 ! Code for drive parameters
|
---|
462 | int 0x13 ! dl still contains drive
|
---|
463 | jc geoerr ! No such drive?
|
---|
464 | andb cl, #0x3F ! cl = max sector number (1-origin)
|
---|
465 | incb dh ! dh = 1 + max head number (0-origin)
|
---|
466 | geoboth:
|
---|
467 | movb sectors, cl ! Sectors per track
|
---|
468 | movb al, cl ! al = sectors per track
|
---|
469 | mulb dh ! ax = heads * sectors
|
---|
470 | mov secspcyl, ax ! Sectors per cylinder = heads * sectors
|
---|
471 | movb dev_state, #1 ! Device state is "open"
|
---|
472 | xor ax, ax ! Code for success
|
---|
473 | geodone:
|
---|
474 | pop di
|
---|
475 | pop es ! Restore di and es registers
|
---|
476 | ret
|
---|
477 | geoerr: movb al, ah
|
---|
478 | xorb ah, ah ! ax = BIOS error code
|
---|
479 | jmp geodone
|
---|
480 | .data
|
---|
481 | seclist:
|
---|
482 | .data1 18, 15, 9 ! 1.44M, 1.2M, and 360K/720K floppy sec/track
|
---|
483 | .text
|
---|
484 |
|
---|
485 | ! int dev_close(void);
|
---|
486 | ! Close the current device. Under the BIOS this does nothing much.
|
---|
487 | .define _dev_close
|
---|
488 | _dev_close:
|
---|
489 | xor ax, ax
|
---|
490 | movb dev_state, al ! State is "closed"
|
---|
491 | ret
|
---|
492 |
|
---|
493 | ! Reset the disks if needed. Minix may have messed things up.
|
---|
494 | dev_reset:
|
---|
495 | cmpb dev_state, #0 ! Need reset if dev_state < 0
|
---|
496 | jge 0f
|
---|
497 | xorb ah, ah ! Reset (ah = 0)
|
---|
498 | movb dl, #0x80 ! All disks
|
---|
499 | int 0x13
|
---|
500 | movb dev_state, #0 ! State is "closed"
|
---|
501 | 0: ret
|
---|
502 |
|
---|
503 | ! int dev_boundary(u32_t sector);
|
---|
504 | ! True if a sector is on a boundary, i.e. sector % sectors == 0.
|
---|
505 | .define _dev_boundary
|
---|
506 | _dev_boundary:
|
---|
507 | mov bx, sp
|
---|
508 | xor dx, dx
|
---|
509 | mov ax, 4(bx) ! divide high half of sector number
|
---|
510 | div sectors
|
---|
511 | mov ax, 2(bx) ! divide low half of sector number
|
---|
512 | div sectors ! dx = sector % sectors
|
---|
513 | sub dx, #1 ! CF = dx == 0
|
---|
514 | sbb ax, ax ! ax = -CF
|
---|
515 | neg ax ! ax = (sector % sectors) == 0
|
---|
516 | ret
|
---|
517 |
|
---|
518 | ! int readsectors(u32_t bufaddr, u32_t sector, u8_t count)
|
---|
519 | ! int writesectors(u32_t bufaddr, u32_t sector, u8_t count)
|
---|
520 | ! Read/write several sectors from/to disk or floppy. The buffer must
|
---|
521 | ! be between 64K boundaries! Count must fit in a byte. The external
|
---|
522 | ! variables _device, sectors and secspcyl describe the disk and its
|
---|
523 | ! geometry. Returns 0 for success, otherwise the BIOS error code.
|
---|
524 | !
|
---|
525 | .define _readsectors, _writesectors
|
---|
526 | _writesectors:
|
---|
527 | push bp
|
---|
528 | mov bp, sp
|
---|
529 | movb 13(bp), #0x03 ! Code for a disk write
|
---|
530 | jmp rwsec
|
---|
531 | _readsectors:
|
---|
532 | push bp
|
---|
533 | mov bp, sp
|
---|
534 | movb 13(bp), #0x02 ! Code for a disk read
|
---|
535 | rwsec: push si
|
---|
536 | push di
|
---|
537 | push es
|
---|
538 | cmpb dev_state, #0 ! Device state?
|
---|
539 | jg 0f ! >0 if open
|
---|
540 | call _dev_open ! Initialize
|
---|
541 | test ax, ax
|
---|
542 | jnz badopen
|
---|
543 | 0: mov ax, 4(bp)
|
---|
544 | mov dx, 6(bp)
|
---|
545 | call abs2seg
|
---|
546 | mov bx, ax
|
---|
547 | mov es, dx ! es:bx = bufaddr
|
---|
548 | mov di, #3 ! Execute 3 resets on floppy error
|
---|
549 | cmpb _device, #0x80
|
---|
550 | jb nohd
|
---|
551 | mov di, #1 ! But only 1 reset on hard disk error
|
---|
552 | nohd: cmpb 12(bp), #0 ! count equals zero?
|
---|
553 | jz done
|
---|
554 | more: mov ax, 8(bp)
|
---|
555 | mov dx, 10(bp) ! dx:ax = abs sector. Divide it by sectors/cyl
|
---|
556 | cmp dx, #[1024*255*63-255]>>16 ! Near 8G limit?
|
---|
557 | jae bigdisk
|
---|
558 | div secspcyl ! ax = cylinder, dx = sector within cylinder
|
---|
559 | xchg ax, dx ! ax = sector within cylinder, dx = cylinder
|
---|
560 | movb ch, dl ! ch = low 8 bits of cylinder
|
---|
561 | divb sectors ! al = head, ah = sector (0-origin)
|
---|
562 | xorb dl, dl ! About to shift bits 8-9 of cylinder into dl
|
---|
563 | shr dx, #1
|
---|
564 | shr dx, #1 ! dl[6..7] = high cylinder
|
---|
565 | orb dl, ah ! dl[0..5] = sector (0-origin)
|
---|
566 | movb cl, dl ! cl[0..5] = sector, cl[6..7] = high cyl
|
---|
567 | incb cl ! cl[0..5] = sector (1-origin)
|
---|
568 | movb dh, al ! dh = head
|
---|
569 | movb dl, _device ! dl = device to use
|
---|
570 | movb al, sectors ! Sectors per track - Sector number (0-origin)
|
---|
571 | subb al, ah ! = Sectors left on this track
|
---|
572 | cmpb al, 12(bp) ! Compare with # sectors to transfer
|
---|
573 | jbe doit ! Can't go past the end of a cylinder?
|
---|
574 | movb al, 12(bp) ! 12(bp) < sectors left on this track
|
---|
575 | doit: movb ah, 13(bp) ! Code for disk read (0x02) or write (0x03)
|
---|
576 | push ax ! Save al = sectors to read
|
---|
577 | int 0x13 ! call the BIOS to do the transfer
|
---|
578 | pop cx ! Restore al in cl
|
---|
579 | jmp rdeval
|
---|
580 | bigdisk:
|
---|
581 | mov si, #ext_rw ! si = extended read/write parameter packet
|
---|
582 | movb cl, 12(bp)
|
---|
583 | movb 2(si), cl ! Fill in # blocks to transfer
|
---|
584 | mov 4(si), bx ! Buffer address = es:bx
|
---|
585 | mov 6(si), es
|
---|
586 | mov 8(si), ax ! Starting block number = dx:ax
|
---|
587 | mov 10(si), dx
|
---|
588 | movb dl, _device ! dl = device to use
|
---|
589 | mov ax, #0x4000 ! This, or-ed with 0x02 or 0x03 becomes
|
---|
590 | orb ah, 13(bp) ! extended read (0x4200) or write (0x4300)
|
---|
591 | int 0x13
|
---|
592 | !jmp rdeval
|
---|
593 | rdeval:
|
---|
594 | jc ioerr ! I/O error
|
---|
595 | movb al, cl ! Restore al = sectors read
|
---|
596 | addb bh, al ! bx += 2 * al * 256 (add bytes transferred)
|
---|
597 | addb bh, al ! es:bx = where next sector is located
|
---|
598 | add 8(bp), ax ! Update address by sectors transferred
|
---|
599 | adc 10(bp), #0 ! Don't forget high word
|
---|
600 | subb 12(bp), al ! Decrement sector count by sectors transferred
|
---|
601 | jnz more ! Not all sectors have been transferred
|
---|
602 | done: xorb ah, ah ! No error here!
|
---|
603 | jmp finish
|
---|
604 | ioerr: cmpb ah, #0x80 ! Disk timed out? (Floppy drive empty)
|
---|
605 | je finish
|
---|
606 | cmpb ah, #0x03 ! Disk write protected?
|
---|
607 | je finish
|
---|
608 | dec di ! Do we allow another reset?
|
---|
609 | jl finish ! No, report the error
|
---|
610 | xorb ah, ah ! Code for a reset (0)
|
---|
611 | int 0x13
|
---|
612 | jnc more ! Succesful reset, try request again
|
---|
613 | finish: movb al, ah
|
---|
614 | xorb ah, ah ! ax = error number
|
---|
615 | badopen:pop es
|
---|
616 | pop di
|
---|
617 | pop si
|
---|
618 | pop bp
|
---|
619 | ret
|
---|
620 | .data
|
---|
621 | .align 4
|
---|
622 | ! Extended read/write commands require a parameter packet.
|
---|
623 | ext_rw:
|
---|
624 | .data1 0x10 ! Length of extended r/w packet
|
---|
625 | .data1 0 ! Reserved
|
---|
626 | .data2 0 ! Blocks to transfer (to be filled in)
|
---|
627 | .data2 0 ! Buffer address offset (tbfi)
|
---|
628 | .data2 0 ! Buffer address segment (tbfi)
|
---|
629 | .data4 0 ! Starting block number low 32 bits (tbfi)
|
---|
630 | .data4 0 ! Starting block number high 32 bits
|
---|
631 | .text
|
---|
632 |
|
---|
633 | ! int getch(void);
|
---|
634 | ! Read a character from the keyboard, and check for an expired timer.
|
---|
635 | ! A carriage return is changed into a linefeed for UNIX compatibility.
|
---|
636 | .define _getch
|
---|
637 | _getch:
|
---|
638 | xor ax, ax
|
---|
639 | xchg ax, unchar ! Ungotten character?
|
---|
640 | test ax, ax
|
---|
641 | jnz gotch
|
---|
642 | getch:
|
---|
643 | hlt ! Play dead until interrupted (see pause())
|
---|
644 | movb ah, #0x01 ! Keyboard status
|
---|
645 | int 0x16
|
---|
646 | jz 0f ! Nothing typed
|
---|
647 | xorb ah, ah ! Read character from keyboard
|
---|
648 | int 0x16
|
---|
649 | jmp press ! Keypress
|
---|
650 | 0: mov dx, line ! Serial line?
|
---|
651 | test dx, dx
|
---|
652 | jz 0f
|
---|
653 | add dx, #5 ! Line Status Register
|
---|
654 | inb dx
|
---|
655 | testb al, #0x01 ! Data Ready?
|
---|
656 | jz 0f
|
---|
657 | mov dx, line
|
---|
658 | !add dx, 0 ! Receive Buffer Register
|
---|
659 | inb dx ! Get character
|
---|
660 | jmp press
|
---|
661 | 0: call _expired ! Timer expired?
|
---|
662 | test ax, ax
|
---|
663 | jz getch
|
---|
664 | mov ax, #ESC ! Return ESC
|
---|
665 | ret
|
---|
666 | press:
|
---|
667 | cmpb al, #0x0D ! Carriage return?
|
---|
668 | jnz nocr
|
---|
669 | movb al, #0x0A ! Change to linefeed
|
---|
670 | nocr: cmpb al, #ESC ! Escape typed?
|
---|
671 | jne noesc
|
---|
672 | inc escape ! Set flag
|
---|
673 | noesc: xorb ah, ah ! ax = al
|
---|
674 | gotch: ret
|
---|
675 |
|
---|
676 | ! int ungetch(void);
|
---|
677 | ! Return a character to undo a getch().
|
---|
678 | .define _ungetch
|
---|
679 | _ungetch:
|
---|
680 | mov bx, sp
|
---|
681 | mov ax, 2(bx)
|
---|
682 | mov unchar, ax
|
---|
683 | ret
|
---|
684 |
|
---|
685 | ! int escape(void);
|
---|
686 | ! True if ESC has been typed.
|
---|
687 | .define _escape
|
---|
688 | _escape:
|
---|
689 | movb ah, #0x01 ! Keyboard status
|
---|
690 | int 0x16
|
---|
691 | jz escflg ! Keypress?
|
---|
692 | cmpb al, #ESC ! Escape typed?
|
---|
693 | jne escflg
|
---|
694 | xorb ah, ah ! Discard the escape
|
---|
695 | int 0x16
|
---|
696 | inc escape ! Set flag
|
---|
697 | escflg: xor ax, ax
|
---|
698 | xchg ax, escape ! Escape typed flag
|
---|
699 | ret
|
---|
700 |
|
---|
701 | ! int putch(int c);
|
---|
702 | ! Write a character in teletype mode. The putk synonym is
|
---|
703 | ! for the kernel printf function that uses it.
|
---|
704 | ! Newlines are automatically preceded by a carriage return.
|
---|
705 | !
|
---|
706 | .define _putch, _putk
|
---|
707 | _putch:
|
---|
708 | _putk: mov bx, sp
|
---|
709 | movb al, 2(bx) ! al = character to be printed
|
---|
710 | testb al, al ! Kernel printf adds a null char to flush queue
|
---|
711 | jz nulch
|
---|
712 | cmpb al, #0x0A ! al = newline?
|
---|
713 | jnz putc
|
---|
714 | movb al, #0x0D
|
---|
715 | call putc ! putc('\r')
|
---|
716 | movb al, #0x0A ! Restore the '\n' and print it
|
---|
717 | putc: movb ah, #0x0E ! Print character in teletype mode
|
---|
718 | mov bx, #0x0001 ! Page 0, foreground color
|
---|
719 | int 0x10
|
---|
720 | mov bx, line ! Serial line?
|
---|
721 | test bx, bx
|
---|
722 | jz nulch
|
---|
723 | push ax ! Save character to print
|
---|
724 | call _get_tick ! Current clock tick counter
|
---|
725 | mov cx, ax
|
---|
726 | add cx, #2 ! Don't want to see it count twice
|
---|
727 | 1: lea dx, 5(bx) ! Line Status Register
|
---|
728 | inb dx
|
---|
729 | testb al, #0x20 ! Transmitter Holding Register Empty?
|
---|
730 | jnz 0f
|
---|
731 | call _get_tick
|
---|
732 | cmp ax, cx ! Clock ticked more than once?
|
---|
733 | jne 1b
|
---|
734 | 0: pop ax ! Restore character to print
|
---|
735 | mov dx, bx ! Transmit Holding Register
|
---|
736 | outb dx ! Send character down the serial line
|
---|
737 | nulch: ret
|
---|
738 |
|
---|
739 | ! void pause(void);
|
---|
740 | ! Wait for an interrupt using the HLT instruction. This either saves
|
---|
741 | ! power, or tells an x86 emulator that nothing is happening right now.
|
---|
742 | .define _pause
|
---|
743 | _pause:
|
---|
744 | hlt
|
---|
745 | ret
|
---|
746 |
|
---|
747 | ! void set_mode(unsigned mode);
|
---|
748 | ! void clear_screen(void);
|
---|
749 | ! Set video mode / clear the screen.
|
---|
750 | .define _set_mode, _clear_screen
|
---|
751 | _set_mode:
|
---|
752 | mov bx, sp
|
---|
753 | mov ax, 2(bx) ! Video mode
|
---|
754 | cmp ax, cur_vid_mode
|
---|
755 | je modeok ! Mode already as requested?
|
---|
756 | mov cur_vid_mode, ax
|
---|
757 | _clear_screen:
|
---|
758 | xor ax, ax
|
---|
759 | mov es, ax ! es = Vector segment
|
---|
760 | mov ax, cur_vid_mode
|
---|
761 | movb ch, ah ! Copy of the special flags
|
---|
762 | andb ah, #0x0F ! Test bits 8-11, clear special flags
|
---|
763 | jnz xvesa ! VESA extended mode?
|
---|
764 | int 0x10 ! Reset video (ah = 0)
|
---|
765 | jmp md_480
|
---|
766 | xvesa: mov bx, ax ! bx = extended mode
|
---|
767 | mov ax, #0x4F02 ! Reset video
|
---|
768 | int 0x10
|
---|
769 | md_480: ! Basic video mode is set, now build on it
|
---|
770 | testb ch, #0x20 ! 480 scan lines requested?
|
---|
771 | jz md_14pt
|
---|
772 | mov dx, #0x3CC ! Get CRTC port
|
---|
773 | inb dx
|
---|
774 | movb dl, #0xD4
|
---|
775 | testb al, #1 ! Mono or color?
|
---|
776 | jnz 0f
|
---|
777 | movb dl, #0xB4
|
---|
778 | 0: mov ax, #0x110C ! Vertical sync end (also unlocks CR0-7)
|
---|
779 | call out2
|
---|
780 | mov ax, #0x060B ! Vertical total
|
---|
781 | call out2
|
---|
782 | mov ax, #0x073E ! (Vertical) overflow
|
---|
783 | call out2
|
---|
784 | mov ax, #0x10EA ! Vertical sync start
|
---|
785 | call out2
|
---|
786 | mov ax, #0x12DF ! Vertical display end
|
---|
787 | call out2
|
---|
788 | mov ax, #0x15E7 ! Vertical blank start
|
---|
789 | call out2
|
---|
790 | mov ax, #0x1604 ! Vertical blank end
|
---|
791 | call out2
|
---|
792 | push dx
|
---|
793 | movb dl, #0xCC ! Misc output register (read)
|
---|
794 | inb dx
|
---|
795 | movb dl, #0xC2 ! (write)
|
---|
796 | andb al, #0x0D ! Preserve clock select bits and color bit
|
---|
797 | orb al, #0xE2 ! Set correct sync polarity
|
---|
798 | outb dx
|
---|
799 | pop dx ! Index register still in dx
|
---|
800 | md_14pt:
|
---|
801 | testb ch, #0x40 ! 9x14 point font requested?
|
---|
802 | jz md_8pt
|
---|
803 | mov ax, #0x1111 ! Load ROM 9 by 14 font
|
---|
804 | xorb bl, bl ! Load block 0
|
---|
805 | int 0x10
|
---|
806 | testb ch, #0x20 ! 480 scan lines?
|
---|
807 | jz md_8pt
|
---|
808 | mov ax, #0x12DB ! VGA vertical display end
|
---|
809 | call out2
|
---|
810 | eseg movb 0x0484, #33 ! Tell BIOS the last line number
|
---|
811 | md_8pt:
|
---|
812 | testb ch, #0x80 ! 8x8 point font requested?
|
---|
813 | jz setcur
|
---|
814 | mov ax, #0x1112 ! Load ROM 8 by 8 font
|
---|
815 | xorb bl, bl ! Load block 0
|
---|
816 | int 0x10
|
---|
817 | testb ch, #0x20 ! 480 scan lines?
|
---|
818 | jz setcur
|
---|
819 | mov ax, #0x12DF ! VGA vertical display end
|
---|
820 | call out2
|
---|
821 | eseg movb 0x0484, #59 ! Tell BIOS the last line number
|
---|
822 | setcur:
|
---|
823 | xor dx, dx ! dl = column = 0, dh = row = 0
|
---|
824 | xorb bh, bh ! Page 0
|
---|
825 | movb ah, #0x02 ! Set cursor position
|
---|
826 | int 0x10
|
---|
827 | push ss
|
---|
828 | pop es ! Restore es
|
---|
829 | modeok: ret
|
---|
830 |
|
---|
831 | ! Out to the usual [index, data] port pair that are common for VGA devices
|
---|
832 | ! dx = port, ah = index, al = data.
|
---|
833 | out2:
|
---|
834 | push dx
|
---|
835 | push ax
|
---|
836 | movb al, ah
|
---|
837 | outb dx ! Set index
|
---|
838 | inc dx
|
---|
839 | pop ax
|
---|
840 | outb dx ! Send data
|
---|
841 | pop dx
|
---|
842 | ret
|
---|
843 |
|
---|
844 | restore_video: ! To restore the video mode on exit
|
---|
845 | mov ax, old_vid_mode
|
---|
846 | push ax
|
---|
847 | call _set_mode
|
---|
848 | pop ax
|
---|
849 | ret
|
---|
850 |
|
---|
851 | ! void serial_init(int line)
|
---|
852 | ! Initialize copying console I/O to a serial line.
|
---|
853 | .define _serial_init
|
---|
854 | _serial_init:
|
---|
855 | mov bx, sp
|
---|
856 | mov dx, 2(bx) ! Line number
|
---|
857 | push ds
|
---|
858 | xor ax, ax
|
---|
859 | mov ds, ax ! Vector and BIOS data segment
|
---|
860 | mov bx, dx ! Line number
|
---|
861 | shl bx, #1 ! Word offset
|
---|
862 | mov bx, 0x0400(bx) ! I/O port for the given line
|
---|
863 | pop ds
|
---|
864 | mov line, bx ! Remember I/O port
|
---|
865 | serial_init:
|
---|
866 | mov bx, line
|
---|
867 | test bx, bx ! I/O port must be nonzero
|
---|
868 | jz 0f
|
---|
869 | mov ax, #0x00E3 ! 9600 N-8-1
|
---|
870 | int 0x14 ! Initialize serial line dx
|
---|
871 | lea dx, 4(bx) ! Modem Control Register
|
---|
872 | movb al, #0x0B ! DTR, RTS, OUT2
|
---|
873 | outb dx
|
---|
874 | 0: ret
|
---|
875 |
|
---|
876 | ! u32_t get_tick(void);
|
---|
877 | ! Return the current value of the clock tick counter. This counter
|
---|
878 | ! increments 18.2 times per second. Poll it to do delays. Does not
|
---|
879 | ! work on the original PC, but works on the PC/XT.
|
---|
880 | .define _get_tick
|
---|
881 | _get_tick:
|
---|
882 | push cx
|
---|
883 | xorb ah, ah ! Code for get tick count
|
---|
884 | int 0x1A
|
---|
885 | mov ax, dx
|
---|
886 | mov dx, cx ! dx:ax = cx:dx = tick count
|
---|
887 | pop cx
|
---|
888 | ret
|
---|
889 |
|
---|
890 |
|
---|
891 | ! Functions used to obtain info about the hardware. Boot uses this information
|
---|
892 | ! itself, but will also pass them on to a pure 386 kernel, because one can't
|
---|
893 | ! make BIOS calls from protected mode. The video type could probably be
|
---|
894 | ! determined by the kernel too by looking at the hardware, but there is a small
|
---|
895 | ! chance on errors that the monitor allows you to correct by setting variables.
|
---|
896 |
|
---|
897 | .define _get_bus ! returns type of system bus
|
---|
898 | .define _get_video ! returns type of display
|
---|
899 |
|
---|
900 | ! u16_t get_bus(void)
|
---|
901 | ! Return type of system bus, in order: XT, AT, MCA.
|
---|
902 | _get_bus:
|
---|
903 | call _getprocessor
|
---|
904 | xor dx, dx ! Assume XT
|
---|
905 | cmp ax, #286 ! An AT has at least a 286
|
---|
906 | jb got_bus
|
---|
907 | inc dx ! Assume AT
|
---|
908 | movb ah, #0xC0 ! Code for get configuration
|
---|
909 | int 0x15
|
---|
910 | jc got_bus ! Carry clear and ah = 00 if supported
|
---|
911 | testb ah, ah
|
---|
912 | jne got_bus
|
---|
913 | eseg
|
---|
914 | movb al, 5(bx) ! Load feature byte #1
|
---|
915 | inc dx ! Assume MCA
|
---|
916 | testb al, #0x02 ! Test bit 1 - "bus is Micro Channel"
|
---|
917 | jnz got_bus
|
---|
918 | dec dx ! Assume AT
|
---|
919 | testb al, #0x40 ! Test bit 6 - "2nd 8259 installed"
|
---|
920 | jnz got_bus
|
---|
921 | dec dx ! It is an XT
|
---|
922 | got_bus:
|
---|
923 | push ds
|
---|
924 | pop es ! Restore es
|
---|
925 | mov ax, dx ! Return bus code
|
---|
926 | mov bus, ax ! Keep bus code, A20 handler likes to know
|
---|
927 | ret
|
---|
928 |
|
---|
929 | ! u16_t get_video(void)
|
---|
930 | ! Return type of display, in order: MDA, CGA, mono EGA, color EGA,
|
---|
931 | ! mono VGA, color VGA.
|
---|
932 | _get_video:
|
---|
933 | mov ax, #0x1A00 ! Function 1A returns display code
|
---|
934 | int 0x10 ! al = 1A if supported
|
---|
935 | cmpb al, #0x1A
|
---|
936 | jnz no_dc ! No display code function supported
|
---|
937 |
|
---|
938 | mov ax, #2
|
---|
939 | cmpb bl, #5 ! Is it a monochrome EGA?
|
---|
940 | jz got_video
|
---|
941 | inc ax
|
---|
942 | cmpb bl, #4 ! Is it a color EGA?
|
---|
943 | jz got_video
|
---|
944 | inc ax
|
---|
945 | cmpb bl, #7 ! Is it a monochrome VGA?
|
---|
946 | jz got_video
|
---|
947 | inc ax
|
---|
948 | cmpb bl, #8 ! Is it a color VGA?
|
---|
949 | jz got_video
|
---|
950 |
|
---|
951 | no_dc: movb ah, #0x12 ! Get information about the EGA
|
---|
952 | movb bl, #0x10
|
---|
953 | int 0x10
|
---|
954 | cmpb bl, #0x10 ! Did it come back as 0x10? (No EGA)
|
---|
955 | jz no_ega
|
---|
956 |
|
---|
957 | mov ax, #2
|
---|
958 | cmpb bh, #1 ! Is it monochrome?
|
---|
959 | jz got_video
|
---|
960 | inc ax
|
---|
961 | jmp got_video
|
---|
962 |
|
---|
963 | no_ega: int 0x11 ! Get bit pattern for equipment
|
---|
964 | and ax, #0x30 ! Isolate color/mono field
|
---|
965 | sub ax, #0x30
|
---|
966 | jz got_video ! Is it an MDA?
|
---|
967 | mov ax, #1 ! No it's CGA
|
---|
968 |
|
---|
969 | got_video:
|
---|
970 | ret
|
---|
971 |
|
---|
972 |
|
---|
973 | ! Functions to leave the boot monitor.
|
---|
974 | .define _bootstrap ! Call another bootstrap
|
---|
975 | .define _minix ! Call Minix
|
---|
976 |
|
---|
977 | ! void _bootstrap(int device, struct part_entry *entry)
|
---|
978 | ! Call another bootstrap routine to boot MS-DOS for instance. (No real
|
---|
979 | ! need for that anymore, now that you can format floppies under Minix).
|
---|
980 | ! The bootstrap must have been loaded at BOOTSEG from "device".
|
---|
981 | _bootstrap:
|
---|
982 | call restore_video
|
---|
983 | mov bx, sp
|
---|
984 | movb dl, 2(bx) ! Device to boot from
|
---|
985 | mov si, 4(bx) ! ds:si = partition table entry
|
---|
986 | xor ax, ax
|
---|
987 | mov es, ax ! Vector segment
|
---|
988 | mov di, #BUFFER ! es:di = buffer in low core
|
---|
989 | mov cx, #PENTRYSIZE ! cx = size of partition table entry
|
---|
990 | rep movsb ! Copy the entry to low core
|
---|
991 | mov si, #BUFFER ! es:si = partition table entry
|
---|
992 | mov ds, ax ! Some bootstraps need zero segment registers
|
---|
993 | cli
|
---|
994 | mov ss, ax
|
---|
995 | mov sp, #BOOTOFF ! This should do it
|
---|
996 | sti
|
---|
997 | jmpf BOOTOFF, 0 ! Back to where the BIOS loads the boot code
|
---|
998 |
|
---|
999 | ! void minix(u32_t koff, u32_t kcs, u32_t kds,
|
---|
1000 | ! char *bootparams, size_t paramsize, u32_t aout);
|
---|
1001 | ! Call Minix.
|
---|
1002 | _minix:
|
---|
1003 | push bp
|
---|
1004 | mov bp, sp ! Pointer to arguments
|
---|
1005 |
|
---|
1006 | mov dx, #0x03F2 ! Floppy motor drive control bits
|
---|
1007 | movb al, #0x0C ! Bits 4-7 for floppy 0-3 are off
|
---|
1008 | outb dx ! Kill the motors
|
---|
1009 | push ds
|
---|
1010 | xor ax, ax ! Vector & BIOS data segments
|
---|
1011 | mov ds, ax
|
---|
1012 | andb 0x043F, #0xF0 ! Clear diskette motor status bits of BIOS
|
---|
1013 | pop ds
|
---|
1014 | cli ! No more interruptions
|
---|
1015 |
|
---|
1016 | test _k_flags, #K_I386 ! Switch to 386 mode?
|
---|
1017 | jnz minix386
|
---|
1018 |
|
---|
1019 | ! Call Minix in real mode.
|
---|
1020 | minix86:
|
---|
1021 | test _k_flags, #K_MEML ! New memory arrangements?
|
---|
1022 | jz 0f
|
---|
1023 | push 22(bp) ! Address of a.out headers
|
---|
1024 | push 20(bp)
|
---|
1025 | 0:
|
---|
1026 | push 18(bp) ! # bytes of boot parameters
|
---|
1027 | push 16(bp) ! Address of boot parameters
|
---|
1028 |
|
---|
1029 | test _k_flags, #K_RET ! Can the kernel return?
|
---|
1030 | jz noret86
|
---|
1031 | xor dx, dx ! If little ext mem then monitor not preserved
|
---|
1032 | xor ax, ax
|
---|
1033 | cmp _mon_return, ax ! Minix can return to the monitor?
|
---|
1034 | jz 0f
|
---|
1035 | mov dx, cs ! Monitor far return address
|
---|
1036 | mov ax, #ret86
|
---|
1037 | 0: push dx ! Push monitor far return address or zero
|
---|
1038 | push ax
|
---|
1039 | noret86:
|
---|
1040 |
|
---|
1041 | mov ax, 8(bp)
|
---|
1042 | mov dx, 10(bp)
|
---|
1043 | call abs2seg
|
---|
1044 | push dx ! Kernel code segment
|
---|
1045 | push 4(bp) ! Kernel code offset
|
---|
1046 | mov ax, 12(bp)
|
---|
1047 | mov dx, 14(bp)
|
---|
1048 | call abs2seg
|
---|
1049 | mov ds, dx ! Kernel data segment
|
---|
1050 | mov es, dx ! Set es to kernel data too
|
---|
1051 | retf ! Make a far call to the kernel
|
---|
1052 |
|
---|
1053 | ! Call Minix in 386 mode.
|
---|
1054 | minix386:
|
---|
1055 | cseg mov cs_real-2, cs ! Patch CS and DS into the instructions that
|
---|
1056 | cseg mov ds_real-2, ds ! reload them when switching back to real mode
|
---|
1057 | .data1 0x0F,0x20,0xC0 ! mov eax, cr0
|
---|
1058 | orb al, #0x01 ! Set PE (protection enable) bit
|
---|
1059 | .data1 o32
|
---|
1060 | mov msw, ax ! Save as protected mode machine status word
|
---|
1061 |
|
---|
1062 | mov dx, ds ! Monitor ds
|
---|
1063 | mov ax, #p_gdt ! dx:ax = Global descriptor table
|
---|
1064 | call seg2abs
|
---|
1065 | mov p_gdt_desc+2, ax
|
---|
1066 | movb p_gdt_desc+4, dl ! Set base of global descriptor table
|
---|
1067 |
|
---|
1068 | mov ax, 12(bp)
|
---|
1069 | mov dx, 14(bp) ! Kernel ds (absolute address)
|
---|
1070 | mov p_ds_desc+2, ax
|
---|
1071 | movb p_ds_desc+4, dl ! Set base of kernel data segment
|
---|
1072 |
|
---|
1073 | mov dx, ss ! Monitor ss
|
---|
1074 | xor ax, ax ! dx:ax = Monitor stack segment
|
---|
1075 | call seg2abs ! Minix starts with the stack of the monitor
|
---|
1076 | mov p_ss_desc+2, ax
|
---|
1077 | movb p_ss_desc+4, dl
|
---|
1078 |
|
---|
1079 | mov ax, 8(bp)
|
---|
1080 | mov dx, 10(bp) ! Kernel cs (absolute address)
|
---|
1081 | mov p_cs_desc+2, ax
|
---|
1082 | movb p_cs_desc+4, dl
|
---|
1083 |
|
---|
1084 | mov dx, cs ! Monitor cs
|
---|
1085 | xor ax, ax ! dx:ax = Monitor code segment
|
---|
1086 | call seg2abs
|
---|
1087 | mov p_mcs_desc+2, ax
|
---|
1088 | movb p_mcs_desc+4, dl
|
---|
1089 |
|
---|
1090 | push #MCS_SELECTOR
|
---|
1091 | test _k_flags, #K_INT86 ! Generic INT86 support?
|
---|
1092 | jz 0f
|
---|
1093 | push #int86 ! Far address to INT86 support
|
---|
1094 | jmp 1f
|
---|
1095 | 0: push #bios13 ! Far address to BIOS int 13 support
|
---|
1096 | 1:
|
---|
1097 | test _k_flags, #K_MEML ! New memory arrangements?
|
---|
1098 | jz 0f
|
---|
1099 | .data1 o32
|
---|
1100 | push 20(bp) ! Address of a.out headers
|
---|
1101 | 0:
|
---|
1102 | push #0
|
---|
1103 | push 18(bp) ! 32 bit size of parameters on stack
|
---|
1104 | push #0
|
---|
1105 | push 16(bp) ! 32 bit address of parameters (ss relative)
|
---|
1106 |
|
---|
1107 | test _k_flags, #K_RET ! Can the kernel return?
|
---|
1108 | jz noret386
|
---|
1109 | push #MCS_SELECTOR
|
---|
1110 | push #ret386 ! Monitor far return address
|
---|
1111 | noret386:
|
---|
1112 |
|
---|
1113 | push #0
|
---|
1114 | push #CS_SELECTOR
|
---|
1115 | push 6(bp)
|
---|
1116 | push 4(bp) ! 32 bit far address to kernel entry point
|
---|
1117 |
|
---|
1118 | call real2prot ! Switch to protected mode
|
---|
1119 | mov ax, #DS_SELECTOR ! Kernel data
|
---|
1120 | mov ds, ax
|
---|
1121 | mov ax, #ES_SELECTOR ! Flat 4 Gb
|
---|
1122 | mov es, ax
|
---|
1123 | .data1 o32 ! Make a far call to the kernel
|
---|
1124 | retf
|
---|
1125 |
|
---|
1126 | ! Minix-86 returns here on a halt or reboot.
|
---|
1127 | ret86:
|
---|
1128 | mov _reboot_code+0, ax
|
---|
1129 | mov _reboot_code+2, dx ! Return value (obsolete method)
|
---|
1130 | jmp return
|
---|
1131 |
|
---|
1132 | ! Minix-386 returns here on a halt or reboot.
|
---|
1133 | ret386:
|
---|
1134 | .data1 o32
|
---|
1135 | mov _reboot_code, ax ! Return value (obsolete method)
|
---|
1136 | call prot2real ! Switch to real mode
|
---|
1137 |
|
---|
1138 | return:
|
---|
1139 | mov sp, bp ! Pop parameters
|
---|
1140 | sti ! Can take interrupts again
|
---|
1141 |
|
---|
1142 | call _get_video ! MDA, CGA, EGA, ...
|
---|
1143 | movb dh, #24 ! dh = row 24
|
---|
1144 | cmp ax, #2 ! At least EGA?
|
---|
1145 | jb is25 ! Otherwise 25 rows
|
---|
1146 | push ds
|
---|
1147 | xor ax, ax ! Vector & BIOS data segments
|
---|
1148 | mov ds, ax
|
---|
1149 | movb dh, 0x0484 ! Number of rows on display minus one
|
---|
1150 | pop ds
|
---|
1151 | is25:
|
---|
1152 | xorb dl, dl ! dl = column 0
|
---|
1153 | xorb bh, bh ! Page 0
|
---|
1154 | movb ah, #0x02 ! Set cursor position
|
---|
1155 | int 0x10
|
---|
1156 |
|
---|
1157 | movb dev_state, #-1 ! Minix may have upset the disks, must reset.
|
---|
1158 | call serial_init ! Likewise with our serial console
|
---|
1159 |
|
---|
1160 | call _getprocessor
|
---|
1161 | cmp ax, #286
|
---|
1162 | jb noclock
|
---|
1163 | xorb al, al
|
---|
1164 | tryclk: decb al
|
---|
1165 | jz noclock
|
---|
1166 | movb ah, #0x02 ! Get real-time clock time (from CMOS clock)
|
---|
1167 | int 0x1A
|
---|
1168 | jc tryclk ! Carry set, not running or being updated
|
---|
1169 | movb al, ch ! ch = hour in BCD
|
---|
1170 | call bcd ! al = (al >> 4) * 10 + (al & 0x0F)
|
---|
1171 | mulb c60 ! 60 minutes in an hour
|
---|
1172 | mov bx, ax ! bx = hour * 60
|
---|
1173 | movb al, cl ! cl = minutes in BCD
|
---|
1174 | call bcd
|
---|
1175 | add bx, ax ! bx = hour * 60 + minutes
|
---|
1176 | movb al, dh ! dh = seconds in BCD
|
---|
1177 | call bcd
|
---|
1178 | xchg ax, bx ! ax = hour * 60 + minutes, bx = seconds
|
---|
1179 | mul c60 ! dx-ax = (hour * 60 + minutes) * 60
|
---|
1180 | add bx, ax
|
---|
1181 | adc dx, #0 ! dx-bx = seconds since midnight
|
---|
1182 | mov ax, dx
|
---|
1183 | mul c19663
|
---|
1184 | xchg ax, bx
|
---|
1185 | mul c19663
|
---|
1186 | add dx, bx ! dx-ax = dx-bx * (0x1800B0 / (2*2*2*2*5))
|
---|
1187 | mov cx, ax ! (0x1800B0 = ticks per day of BIOS clock)
|
---|
1188 | mov ax, dx
|
---|
1189 | xor dx, dx
|
---|
1190 | div c1080
|
---|
1191 | xchg ax, cx
|
---|
1192 | div c1080 ! cx-ax = dx-ax / (24*60*60 / (2*2*2*2*5))
|
---|
1193 | mov dx, ax ! cx-dx = ticks since midnight
|
---|
1194 | movb ah, #0x01 ! Set system time
|
---|
1195 | int 0x1A
|
---|
1196 | noclock:
|
---|
1197 |
|
---|
1198 | pop bp
|
---|
1199 | ret ! Return to monitor as if nothing much happened
|
---|
1200 |
|
---|
1201 | ! Transform BCD number in al to a regular value in ax.
|
---|
1202 | bcd: movb ah, al
|
---|
1203 | shrb ah, #4
|
---|
1204 | andb al, #0x0F
|
---|
1205 | .data1 0xD5,10 ! aad ! ax = (al >> 4) * 10 + (al & 0x0F)
|
---|
1206 | ret ! (BUG: assembler messes up aad & aam!)
|
---|
1207 |
|
---|
1208 | ! Support function for Minix-386 to make a BIOS int 13 call (disk I/O).
|
---|
1209 | bios13:
|
---|
1210 | mov bp, sp
|
---|
1211 | call prot2real
|
---|
1212 | sti ! Enable interrupts
|
---|
1213 |
|
---|
1214 | mov ax, 8(bp) ! Load parameters
|
---|
1215 | mov bx, 10(bp)
|
---|
1216 | mov cx, 12(bp)
|
---|
1217 | mov dx, 14(bp)
|
---|
1218 | mov es, 16(bp)
|
---|
1219 | int 0x13 ! Make the BIOS call
|
---|
1220 | mov 8(bp), ax ! Save results
|
---|
1221 | mov 10(bp), bx
|
---|
1222 | mov 12(bp), cx
|
---|
1223 | mov 14(bp), dx
|
---|
1224 | mov 16(bp), es
|
---|
1225 |
|
---|
1226 | cli ! Disable interrupts
|
---|
1227 | call real2prot
|
---|
1228 | mov ax, #DS_SELECTOR ! Kernel data
|
---|
1229 | mov ds, ax
|
---|
1230 | .data1 o32
|
---|
1231 | retf ! Return to the kernel
|
---|
1232 |
|
---|
1233 | ! Support function for Minix-386 to make an 8086 interrupt call.
|
---|
1234 | int86:
|
---|
1235 | mov bp, sp
|
---|
1236 | call prot2real
|
---|
1237 |
|
---|
1238 | .data1 o32
|
---|
1239 | xor ax, ax
|
---|
1240 | mov es, ax ! Vector & BIOS data segments
|
---|
1241 | .data1 o32
|
---|
1242 | eseg mov 0x046C, ax ! Clear BIOS clock tick counter
|
---|
1243 |
|
---|
1244 | sti ! Enable interrupts
|
---|
1245 |
|
---|
1246 | movb al, #0xCD ! INT instruction
|
---|
1247 | movb ah, 8(bp) ! Interrupt number?
|
---|
1248 | testb ah, ah
|
---|
1249 | jnz 0f ! Nonzero if INT, otherwise far call
|
---|
1250 | push cs
|
---|
1251 | push #intret+2 ! Far return address
|
---|
1252 | .data1 o32
|
---|
1253 | push 12(bp) ! Far driver address
|
---|
1254 | mov ax, #0x90CB ! RETF; NOP
|
---|
1255 | 0:
|
---|
1256 | cseg cmp ax, intret ! Needs to be changed?
|
---|
1257 | je 0f ! If not then avoid a huge I-cache stall
|
---|
1258 | cseg mov intret, ax ! Patch 'INT n' or 'RETF; NOP' into code
|
---|
1259 | jmp .+2 ! Clear instruction queue
|
---|
1260 | 0:
|
---|
1261 | mov ds, 16(bp) ! Load parameters
|
---|
1262 | mov es, 18(bp)
|
---|
1263 | .data1 o32
|
---|
1264 | mov ax, 20(bp)
|
---|
1265 | .data1 o32
|
---|
1266 | mov bx, 24(bp)
|
---|
1267 | .data1 o32
|
---|
1268 | mov cx, 28(bp)
|
---|
1269 | .data1 o32
|
---|
1270 | mov dx, 32(bp)
|
---|
1271 | .data1 o32
|
---|
1272 | mov si, 36(bp)
|
---|
1273 | .data1 o32
|
---|
1274 | mov di, 40(bp)
|
---|
1275 | .data1 o32
|
---|
1276 | mov bp, 44(bp)
|
---|
1277 |
|
---|
1278 | intret: int 0xFF ! Do the interrupt or far call
|
---|
1279 |
|
---|
1280 | .data1 o32 ! Save results
|
---|
1281 | push bp
|
---|
1282 | .data1 o32
|
---|
1283 | pushf
|
---|
1284 | mov bp, sp
|
---|
1285 | .data1 o32
|
---|
1286 | pop 8+8(bp) ! eflags
|
---|
1287 | mov 8+16(bp), ds
|
---|
1288 | mov 8+18(bp), es
|
---|
1289 | .data1 o32
|
---|
1290 | mov 8+20(bp), ax
|
---|
1291 | .data1 o32
|
---|
1292 | mov 8+24(bp), bx
|
---|
1293 | .data1 o32
|
---|
1294 | mov 8+28(bp), cx
|
---|
1295 | .data1 o32
|
---|
1296 | mov 8+32(bp), dx
|
---|
1297 | .data1 o32
|
---|
1298 | mov 8+36(bp), si
|
---|
1299 | .data1 o32
|
---|
1300 | mov 8+40(bp), di
|
---|
1301 | .data1 o32
|
---|
1302 | pop 8+44(bp) ! ebp
|
---|
1303 |
|
---|
1304 | cli ! Disable interrupts
|
---|
1305 |
|
---|
1306 | xor ax, ax
|
---|
1307 | mov ds, ax ! Vector & BIOS data segments
|
---|
1308 | .data1 o32
|
---|
1309 | mov cx, 0x046C ! Collect lost clock ticks in ecx
|
---|
1310 |
|
---|
1311 | mov ax, ss
|
---|
1312 | mov ds, ax ! Restore monitor ds
|
---|
1313 | call real2prot
|
---|
1314 | mov ax, #DS_SELECTOR ! Kernel data
|
---|
1315 | mov ds, ax
|
---|
1316 | .data1 o32
|
---|
1317 | retf ! Return to the kernel
|
---|
1318 |
|
---|
1319 | ! Switch from real to protected mode.
|
---|
1320 | real2prot:
|
---|
1321 | movb ah, #0x02 ! Code for A20 enable
|
---|
1322 | call gate_A20
|
---|
1323 |
|
---|
1324 | lgdt p_gdt_desc ! Global descriptor table
|
---|
1325 | .data1 o32
|
---|
1326 | mov ax, pdbr ! Load page directory base register
|
---|
1327 | .data1 0x0F,0x22,0xD8 ! mov cr3, eax
|
---|
1328 | .data1 0x0F,0x20,0xC0 ! mov eax, cr0
|
---|
1329 | .data1 o32
|
---|
1330 | xchg ax, msw ! Exchange real mode msw for protected mode msw
|
---|
1331 | .data1 0x0F,0x22,0xC0 ! mov cr0, eax
|
---|
1332 | jmpf cs_prot, MCS_SELECTOR ! Set code segment selector
|
---|
1333 | cs_prot:
|
---|
1334 | mov ax, #SS_SELECTOR ! Set data selectors
|
---|
1335 | mov ds, ax
|
---|
1336 | mov es, ax
|
---|
1337 | mov ss, ax
|
---|
1338 | ret
|
---|
1339 |
|
---|
1340 | ! Switch from protected to real mode.
|
---|
1341 | prot2real:
|
---|
1342 | lidt p_idt_desc ! Real mode interrupt vectors
|
---|
1343 | .data1 0x0F,0x20,0xD8 ! mov eax, cr3
|
---|
1344 | .data1 o32
|
---|
1345 | mov pdbr, ax ! Save page directory base register
|
---|
1346 | .data1 0x0F,0x20,0xC0 ! mov eax, cr0
|
---|
1347 | .data1 o32
|
---|
1348 | xchg ax, msw ! Exchange protected mode msw for real mode msw
|
---|
1349 | .data1 0x0F,0x22,0xC0 ! mov cr0, eax
|
---|
1350 | jmpf cs_real, 0xDEAD ! Reload cs register
|
---|
1351 | cs_real:
|
---|
1352 | mov ax, #0xBEEF
|
---|
1353 | ds_real:
|
---|
1354 | mov ds, ax ! Reload data segment registers
|
---|
1355 | mov es, ax
|
---|
1356 | mov ss, ax
|
---|
1357 |
|
---|
1358 | xorb ah, ah ! Code for A20 disable
|
---|
1359 | !jmp gate_A20
|
---|
1360 |
|
---|
1361 | ! Enable (ah = 0x02) or disable (ah = 0x00) the A20 address line.
|
---|
1362 | gate_A20:
|
---|
1363 | cmp bus, #2 ! PS/2 bus?
|
---|
1364 | je gate_PS_A20
|
---|
1365 | call kb_wait
|
---|
1366 | movb al, #0xD1 ! Tell keyboard that a command is coming
|
---|
1367 | outb 0x64
|
---|
1368 | call kb_wait
|
---|
1369 | movb al, #0xDD ! 0xDD = A20 disable code if ah = 0x00
|
---|
1370 | orb al, ah ! 0xDF = A20 enable code if ah = 0x02
|
---|
1371 | outb 0x60
|
---|
1372 | call kb_wait
|
---|
1373 | movb al, #0xFF ! Pulse output port
|
---|
1374 | outb 0x64
|
---|
1375 | call kb_wait ! Wait for the A20 line to settle down
|
---|
1376 | ret
|
---|
1377 | kb_wait:
|
---|
1378 | inb 0x64
|
---|
1379 | testb al, #0x02 ! Keyboard input buffer full?
|
---|
1380 | jnz kb_wait ! If so, wait
|
---|
1381 | ret
|
---|
1382 |
|
---|
1383 | gate_PS_A20: ! The PS/2 can twiddle A20 using port A
|
---|
1384 | inb 0x92 ! Read port A
|
---|
1385 | andb al, #0xFD
|
---|
1386 | orb al, ah ! Set A20 bit to the required state
|
---|
1387 | outb 0x92 ! Write port A
|
---|
1388 | jmp .+2 ! Small delay
|
---|
1389 | A20ok: inb 0x92 ! Check port A
|
---|
1390 | andb al, #0x02
|
---|
1391 | cmpb al, ah ! A20 line settled down to the new state?
|
---|
1392 | jne A20ok ! If not then wait
|
---|
1393 | ret
|
---|
1394 |
|
---|
1395 | ! void int15(bios_env_t *ep)
|
---|
1396 | ! Do an "INT 15" call, primarily for APM (Power Management).
|
---|
1397 | .define _int15
|
---|
1398 | _int15:
|
---|
1399 | push si ! Save callee-save register si
|
---|
1400 | mov si, sp
|
---|
1401 | mov si, 4(si) ! ep
|
---|
1402 | mov ax, (si) ! ep->ax
|
---|
1403 | mov bx, 2(si) ! ep->bx
|
---|
1404 | mov cx, 4(si) ! ep->cx
|
---|
1405 | int 0x15 ! INT 0x15 BIOS call
|
---|
1406 | pushf ! Save flags
|
---|
1407 | mov (si), ax ! ep->ax
|
---|
1408 | mov 2(si), bx ! ep->bx
|
---|
1409 | mov 4(si), cx ! ep->cx
|
---|
1410 | pop 6(si) ! ep->flags
|
---|
1411 | pop si ! Restore
|
---|
1412 | ret
|
---|
1413 |
|
---|
1414 | ! void scan_keyboard(void)
|
---|
1415 | ! Read keyboard character. Needs to be done in case one is waiting.
|
---|
1416 | .define _scan_keyboard
|
---|
1417 | _scan_keyboard:
|
---|
1418 | inb 0x60
|
---|
1419 | inb 0x61
|
---|
1420 | movb ah, al
|
---|
1421 | orb al, #0x80
|
---|
1422 | outb 0x61
|
---|
1423 | movb al, ah
|
---|
1424 | outb 0x61
|
---|
1425 | ret
|
---|
1426 |
|
---|
1427 | .data
|
---|
1428 | .ascii "(null)\0" ! Just in case someone follows a null pointer
|
---|
1429 | .align 2
|
---|
1430 | c60: .data2 60 ! Constants for MUL and DIV
|
---|
1431 | c1024: .data2 1024
|
---|
1432 | c1080: .data2 1080
|
---|
1433 | c19663: .data2 19663
|
---|
1434 |
|
---|
1435 | ! Global descriptor tables.
|
---|
1436 | UNSET = 0 ! Must be computed
|
---|
1437 |
|
---|
1438 | ! For "Extended Memory Block Move".
|
---|
1439 | x_gdt:
|
---|
1440 | x_null_desc:
|
---|
1441 | ! Null descriptor
|
---|
1442 | .data2 0x0000, 0x0000
|
---|
1443 | .data1 0x00, 0x00, 0x00, 0x00
|
---|
1444 | x_gdt_desc:
|
---|
1445 | ! Descriptor for this descriptor table
|
---|
1446 | .data2 6*8-1, UNSET
|
---|
1447 | .data1 UNSET, 0x00, 0x00, 0x00
|
---|
1448 | x_src_desc:
|
---|
1449 | ! Source segment descriptor
|
---|
1450 | .data2 0xFFFF, UNSET
|
---|
1451 | .data1 UNSET, 0x92, 0x00, 0x00
|
---|
1452 | x_dst_desc:
|
---|
1453 | ! Destination segment descriptor
|
---|
1454 | .data2 0xFFFF, UNSET
|
---|
1455 | .data1 UNSET, 0x92, 0x00, 0x00
|
---|
1456 | x_bios_desc:
|
---|
1457 | ! BIOS segment descriptor (scratch for int 0x15)
|
---|
1458 | .data2 UNSET, UNSET
|
---|
1459 | .data1 UNSET, UNSET, UNSET, UNSET
|
---|
1460 | x_ss_desc:
|
---|
1461 | ! BIOS stack segment descriptor (scratch for int 0x15)
|
---|
1462 | .data2 UNSET, UNSET
|
---|
1463 | .data1 UNSET, UNSET, UNSET, UNSET
|
---|
1464 |
|
---|
1465 | ! Protected mode descriptor table.
|
---|
1466 | p_gdt:
|
---|
1467 | p_null_desc:
|
---|
1468 | ! Null descriptor
|
---|
1469 | .data2 0x0000, 0x0000
|
---|
1470 | .data1 0x00, 0x00, 0x00, 0x00
|
---|
1471 | p_gdt_desc:
|
---|
1472 | ! Descriptor for this descriptor table
|
---|
1473 | .data2 8*8-1, UNSET
|
---|
1474 | .data1 UNSET, 0x00, 0x00, 0x00
|
---|
1475 | p_idt_desc:
|
---|
1476 | ! Real mode interrupt descriptor table descriptor
|
---|
1477 | .data2 0x03FF, 0x0000
|
---|
1478 | .data1 0x00, 0x00, 0x00, 0x00
|
---|
1479 | p_ds_desc:
|
---|
1480 | ! Kernel data segment descriptor (4 Gb flat)
|
---|
1481 | .data2 0xFFFF, UNSET
|
---|
1482 | .data1 UNSET, 0x92, 0xCF, 0x00
|
---|
1483 | p_es_desc:
|
---|
1484 | ! Physical memory descriptor (4 Gb flat)
|
---|
1485 | .data2 0xFFFF, 0x0000
|
---|
1486 | .data1 0x00, 0x92, 0xCF, 0x00
|
---|
1487 | p_ss_desc:
|
---|
1488 | ! Monitor data segment descriptor (64 kb flat)
|
---|
1489 | .data2 0xFFFF, UNSET
|
---|
1490 | .data1 UNSET, 0x92, 0x00, 0x00
|
---|
1491 | p_cs_desc:
|
---|
1492 | ! Kernel code segment descriptor (4 Gb flat)
|
---|
1493 | .data2 0xFFFF, UNSET
|
---|
1494 | .data1 UNSET, 0x9A, 0xCF, 0x00
|
---|
1495 | p_mcs_desc:
|
---|
1496 | ! Monitor code segment descriptor (64 kb flat)
|
---|
1497 | .data2 0xFFFF, UNSET
|
---|
1498 | .data1 UNSET, 0x9A, 0x00, 0x00
|
---|
1499 |
|
---|
1500 | .bss
|
---|
1501 | .comm old_vid_mode, 2 ! Video mode at startup
|
---|
1502 | .comm cur_vid_mode, 2 ! Current video mode
|
---|
1503 | .comm dev_state, 2 ! Device state: reset (-1), closed (0), open (1)
|
---|
1504 | .comm sectors, 2 ! # sectors of current device
|
---|
1505 | .comm secspcyl, 2 ! (Sectors * heads) of current device
|
---|
1506 | .comm msw, 4 ! Saved machine status word (cr0)
|
---|
1507 | .comm pdbr, 4 ! Saved page directory base register (cr3)
|
---|
1508 | .comm escape, 2 ! Escape typed?
|
---|
1509 | .comm bus, 2 ! Saved return value of _get_bus
|
---|
1510 | .comm unchar, 2 ! Char returned by ungetch(c)
|
---|
1511 | .comm line, 2 ! Serial line I/O port to copy console I/O to.
|
---|
1512 |
|
---|
1513 |
|
---|