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