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