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