f8bb1df1150dabd14394eb6de1c2a25e76deecb1
[com32] / src / loader.asm
1         section .loader
2
3         extern startup
4         extern _ldr_main_start
5         extern _main_start
6         extern _main_size
7         extern boot_mem_map
8         extern boot_mem_map_size
9
10 %include 'macros.inc'
11 %define CON_SERIAL
12
13         [bits 16]
14         global _start
15 _start:
16         cli
17         mov ax, cs
18         mov ds, ax
19         mov es, ax
20         mov fs, ax      ; this will store the original real mode segment
21         mov ss, ax
22         ; modify the return to real mode jump segment
23         mov [.jmpcs16 + 3], ax
24
25         xor ax, ax
26         mov sp, ax
27
28         ; check for VM86 and abort
29         mov eax, cr0
30         test ax, 1
31         jz .notvm86
32
33         mov si, str_errvm86
34         call printstr
35         jmp exit
36
37 .notvm86:
38         call warning    ; issue a warning and allow the user to abort
39
40 %ifdef CON_SERIAL
41         call setup_serial
42 %endif
43         call enable_a20
44         call detect_memory
45
46         ; calculate GDT linear address
47         xor eax, eax
48         mov ax, cs
49         shl eax, 4
50         add eax, gdt
51         mov [gdt_base], eax
52
53         ; set tmp segment bases to match the linear address of our current seg
54         xor eax, eax
55         mov ax, cs
56         shl eax, 4
57         mov word [gdt + 18h + 2], ax    ; tmp pm code base
58         mov word [gdt + 20h + 2], ax    ; tmp pm data base
59         mov word [gdt + 28h + 2], ax    ; ret-to-realmode code
60         shr eax, 16
61         mov byte [gdt + 18h + 4], al
62         mov byte [gdt + 20h + 4], al
63         mov byte [gdt + 28h + 4], al
64
65         mov si, str_enterpm
66         call printstr
67
68         lgdt [gdt_lim]
69
70         mov eax, cr0
71         or eax, 1
72         mov cr0, eax
73
74         jmp 18h:.pm
75
76         [bits 32]
77 .pm:    mov ax, 20h     ; tmp data selector
78         mov ds, ax
79         mov ax, 10h     ; dest data selector
80         mov es, ax
81
82         ; copy main program high
83         cld
84         mov esi, _ldr_main_start
85         mov edi, _main_start
86         mov ecx, _main_size + 3
87         shr ecx, 2
88         rep movsd
89
90         ; copy memory map
91         mov eax, [mem_map_size]
92         mov [es:boot_mem_map_size], eax
93         mov esi, mem_map
94         mov edi, boot_mem_map
95         mov ecx, 32     ; 128 bytes
96         rep movsd
97
98         mov ax, 10h
99         mov ds, ax
100         mov ss, ax
101         mov esp, _main_start
102
103         call 8:startup
104         cli
105
106         ; return to real mode
107         jmp 28h:.rm
108
109         [bits 16]
110 .rm:    mov eax, cr0
111         and ax, 0xfffe
112         mov cr0, eax
113 .jmpcs16:
114         jmp 42h:.loadcs16       ; 42 seg is modifed at the start
115 .loadcs16:
116         mov ax, fs
117         mov ds, ax
118         mov es, ax
119         mov ss, ax
120
121         ; restore real-mode IVT
122         lidt [rmidt]
123         sti
124
125         mov ax, 3
126         int 10h
127 exit:   mov ax, 4c00h
128         int 21h
129
130 str_errvm86 db 'Error: memory manager detected! Stop it and try again (e.g. emm386 off)',10,0
131 str_enterpm db 'Entering 32bit protected mode ...',10,0
132
133
134         ; warns the user about the experimental and buggy state of this
135         ; protected mode system, and allows aborting if having to reboot later
136         ; is not acceptable.
137 warning:
138         mov si, str_warnmsg
139         call printstr
140         WAITKEY
141         dec al
142         jz exit
143         ret
144
145 str_warnmsg:
146         db 'WARNING: this program uses an experimental protected mode kernel, which is ',10
147         db 'still in a very early stage of development, and will probably not be able to ',10
148         db 'return cleanly to DOS on exit. You might be forced to reboot after quitting!',10
149         db 'If this is not acceptable, press ESC now to abort.',10,10
150         db 'Press ESC to abort and return to DOS, any other key to continue...',10,0
151
152 enable_a20:
153         call test_a20
154         jnc .ret
155
156         mov si, .infomsg
157         call printstr           ; print "Enable A20 line ... "
158
159         call enable_a20_kbd
160         call test_a20
161         jnc .done
162         call enable_a20_fast
163         call test_a20
164         jnc .done
165         mov si, .failstr
166         call printstr
167         mov ax, 4c00h
168         int 21h
169 .done:  mov si, .okstr
170         call printstr
171 .ret:   ret
172
173 .infomsg db 'Enable A20 line:',0
174 .failstr db ' failed.',10,0
175 .okstr  db ' success.',10,0
176
177         ; CF = 1 if A20 test fails (not enabled)
178 test_a20:
179         push ds
180         push es
181         xor ax, ax
182         mov ds, ax
183         not ax
184         mov es, ax
185         mov si, 420h
186         mov di, 430h
187         mov dl, [ds:si]
188         mov dh, [es:di]
189         mov [ds:si], al
190         not ax
191         mov [es:di], al
192         cmp al, [ds:si]
193         clc
194         jnz .done
195         stc
196 .done:  mov [ds:si], dl
197         mov [es:di], dh
198         pop es
199         pop ds
200         ret
201
202 enable_a20_fast:
203         mov si, .info
204         call printstr
205         in al, 92h
206         or al, 2
207         out 92h, al
208         ret
209 .info db ' fast ...',0
210
211 KBC_DATA_PORT equ 0x60
212 KBC_CMD_PORT equ 0x64
213 KBC_STATUS_PORT equ 0x64
214 KBC_CMD_WR_OUTPORT equ 0xd1
215
216 KBC_STAT_IN_FULL equ 2
217
218 enable_a20_kbd:
219         mov si, .info
220         call printstr
221         call kbc_wait_write
222         mov al, KBC_CMD_WR_OUTPORT
223         out KBC_CMD_PORT, al
224         call kbc_wait_write
225         mov al, 0xdf
226         out KBC_DATA_PORT, al
227         ret
228 .info db ' kbd ...',0
229
230 kbc_wait_write:
231         in al, KBC_STATUS_PORT
232         and al, KBC_STAT_IN_FULL
233         jnz kbc_wait_write
234         ret
235
236
237 ; ---------------------- memory detection -----------------------
238
239 detect_memory:
240         mov si, memdet_detram
241         call printstr
242         mov si, memdet_e820_msg
243         call printstr
244         call detect_mem_e820
245         jnc .done
246         mov si, str_fail
247         call printstr
248
249         mov si, memdet_detram
250         call printstr
251         mov si, memdet_e801_msg
252         call printstr
253         call detect_mem_e801
254         jnc .done
255         mov si, str_fail
256         call printstr
257
258         mov si, memdet_detram
259         call printstr
260         mov esi, memdet_88_msg
261         call printstr
262         call detect_mem_88
263         jnc .done
264         mov esi, str_fail
265         call printstr
266
267         mov si, memdet_detram
268         call printstr
269         mov esi, memdet_cmos_msg
270         call printstr
271         call detect_mem_cmos
272         jnc .done
273         mov esi, str_fail
274         call printstr
275
276         mov si, memdet_fail_msg
277         call printstr
278         jmp exit
279 .done:
280         mov si, str_ok
281         call printstr
282         ret
283
284 str_ok db 'OK',10,0
285 str_fail db 'failed',10,0
286 memdet_fail_msg db 'Failed to detect available memory!',10,0
287 memdet_detram   db 'Detecting RAM '
288 memdet_e820_msg db '(BIOS 15h/0xe820)... ',0
289 memdet_e801_msg db '(BIOS 15h/0xe801)... ',0
290 memdet_88_msg   db '(BIOS 15h/0x88, max 64mb)... ',0
291 memdet_cmos_msg db '(CMOS)...',0
292
293         ; detect extended memory using BIOS call 15h/e820
294 detect_mem_e820:
295         mov dword [mem_map_size], 0
296
297         mov edi, .buffer
298         xor ebx, ebx
299         mov edx, 534d4150h
300
301 .looptop:
302         mov eax, 0xe820
303         mov ecx, 24
304         int 15h
305         jc .fail
306         cmp eax, 534d4150h
307         jnz .fail
308
309         ; skip areas starting above 4GB as we won't be able to use them
310         cmp dword [di + 4], 0
311         jnz .skip
312
313         ; only care for type 1 (usable ram), otherwise ignore
314         cmp dword [di + 16], 1
315         jnz .skip
316
317         mov eax, [.buffer]
318         mov esi, mem_map
319         mov ebp, [mem_map_size]
320         mov [ebp * 8 + esi], eax
321
322         ; skip areas with 0 size (also clamp size to 4gb)
323         ; test high 32bits
324         cmp dword [edi + 12], 0
325         jz .highzero
326         ; high part is non-zero, make low part ffffffff
327         xor eax, eax
328         not eax
329         jmp .skiph0
330
331 .highzero:
332         ; if both high and low parts are zero, ignore
333         mov eax, [di + 8]
334         test eax, eax
335         jz .skip
336
337 .skiph0:mov [ebp * 8 + esi + 4], eax
338         inc dword [mem_map_size]
339
340 .skip:
341         ; terminate the loop if ebx was reset to 0
342         test ebx, ebx
343         jz .done
344         jmp .looptop
345 .done:
346         clc
347         ret
348
349 .fail:  ; if size > 0, then it's not a failure, just the end
350         cmp dword [mem_map_size], 0
351         jnz .done
352         stc
353         ret
354
355 .buffer times 32 db 0
356
357         ; detect extended memory using BIOS call 15h/e801
358 detect_mem_e801:
359         mov si, mem_map
360         mov ebp, [mem_map_size]
361         mov dword [ebp], 0
362
363         xor cx, cx
364         xor dx, dx
365         mov ax, 0xe801
366         int 15h
367         jc .fail
368
369         test cx, cx
370         jnz .foo1
371         test ax, ax
372         jz .fail
373         mov cx, ax
374         mov dx, bx
375
376 .foo1:  mov dword [si], 100000h
377         movzx eax, cx
378         ; first size is in KB, convert to bytes
379         shl eax, 10
380         jnc .foo2
381         ; overflow means it's >4GB, clamp to 4GB
382         mov eax, 0xffffffff
383 .foo2:  mov [si + 4], eax
384         inc dword [mem_map_size]
385         test dx, dx
386         jz .done
387         mov dword [si + 8], 1000000h
388         movzx eax, dx
389         ; second size is in 64kb blocks, convert to bytes
390         shl eax, 16
391         jnc .foo3
392         ; overflow means it's >4GB, clamp to 4GB
393         mov eax, 0xffffffff
394 .foo3:  mov [si + 12], eax
395         inc dword [mem_map_size]
396 .done:
397         clc
398         ret
399 .fail:
400         stc
401         ret
402
403 detect_mem_88:
404         ; reportedly some BIOS implementations fail to clear CF on success
405         clc
406         mov ah, 88h
407         int 15h
408         jc .fail
409
410         test ax, ax
411         jz .fail
412
413         ; ax has size in KB, convert to bytes in eax
414         and eax, 0xffff
415         shl eax, 10
416
417         mov esi, mem_map
418         mov dword [si], 100000h
419         mov [si + 4], eax
420
421         mov dword [mem_map_size], 1
422         clc
423         ret
424 .fail:  stc
425         ret
426
427 detect_mem_cmos:
428         mov al, 31h
429         out 70h, al
430         in al, 71h
431         mov ah, al
432         mov al, 30h
433         out 70h, al
434         in al, 71h
435
436         test ax, ax
437         jz .fail
438
439         ; ax has size in KB, convert to bytes in eax
440         and eax, 0xffff
441         shl eax, 10
442
443         mov esi, mem_map
444         mov dword [si], 100000h
445         mov [si + 4], eax
446         mov dword [mem_map_size], 1
447         clc
448         ret
449 .fail:  stc
450         ret
451
452
453         align 4
454 mem_map_size dd 0
455 mem_map times 128 db 0
456
457
458 ; ----------------------- serial console ------------------------
459
460 %ifdef CON_SERIAL
461 setup_serial:
462         ; set clock divisor
463         mov dx, UART_BASE + 3   ; LCTL
464         mov al, 80h             ; DLAB
465         out dx, al
466         mov dx, UART_BASE       ; DIVLO
467         mov al, UART_DIVISOR & 0xff
468         out dx, al
469         inc dx                  ; DIVHI
470         mov al, UART_DIVISOR >> 8
471         out dx, al
472         mov dx, UART_BASE + 3   ; LCTL
473         mov al, 3               ; 8n1
474         out dx, al
475         inc dx                  ; MCTL
476         mov al, 0xb             ; DTR/RTS/OUT2
477         out dx, al
478         ret
479
480 ser_putchar:
481         SER_PUTCHAR
482         ret
483
484 ser_printstr:
485         lodsb
486         test al, al
487         jz .end
488         cmp al, 10
489         jnz .nolf
490         push ax
491         mov al, 13
492         call ser_putchar
493         pop ax
494 .nolf:  call ser_putchar
495         jmp ser_printstr
496 .end:   ret
497
498 %endif ; def CON_SERIAL
499
500
501 printstr:
502         lodsb
503         test al, al
504         jz .end
505         cmp al, 10      ; check for line-feed and insert CR before it
506         jnz .nolf
507         push ax
508 %ifdef CON_SERIAL
509         mov al, 13
510         call ser_putchar
511 %endif
512         mov dl, 13
513         mov ah, 2
514         int 21h
515         pop ax
516 .nolf:
517 %ifdef CON_SERIAL
518         call ser_putchar
519 %endif
520         mov ah, 2
521         mov dl, al
522         int 21h
523         jmp printstr
524 .end:   ret
525
526
527         align 4
528 enterpm dd 0xbad00d     ; space for linear address for far jump to pmode
529 enterpm_sel dw 8        ; selector for far jump to protected mode
530         align 4
531 gdt_lim dw 47           ; GDT limit
532 gdt_base dd 0xbadf00d   ; space for GDT linear address
533
534         align 8
535 gdt:    ; 0: null segment
536         dd 0
537         dd 0
538         ; 1: code - 0/lim:4g, G:4k, 32bit, avl, pres|app, dpl:0, type:code/non-conf/rd (sel: 8)
539         dd 0000ffffh
540         dd 00cf9a00h
541         ; 2: data - 0/lim:4g, G:4k, 32bit, avl, pres|app, dpl:0, type:data/rw (sel: 10h)
542         dd 0000ffffh
543         dd 00cf9200h
544         ; 3: tmp code (will set base before entering pmode) (sel: 18h)
545         dd 0000ffffh
546         dd 00cf9a00h
547         ; 4: tmp data (will set base before entering pmode) (sel: 20h)
548         dd 0000ffffh
549         dd 00cf9200h
550         ; 5: return to real-mode 16bit code segment (sel: 28h)
551         dd 0000ffffh
552         dd 00009a00h
553
554         ; pseudo IDTR descriptor for real-mode IVT at address 0
555         align 4
556         dw 0
557 rmidt:  dw 3ffh         ; IVT limit (1kb / 256 entries)
558         dd 0            ; IVT base 0
559
560 ; vi:set ts=8 sts=8 sw=8 ft=nasm: