:pserver:cvsanon@mok.lvcm.com:/CVS/ReactOS reactos
[reactos.git] / loaders / dos / loadros.asm
1 ;
2 ; Pmode setup stub
3 ; (A20 enable code and PIC reprogram from linux bootsector)
4 ;
5
6 ;
7 ; Base address of the kernel
8 ;
9 LOAD_BASE       equ     0200000h
10
11 ;
12 ; Segment selectors
13 ;
14 %define KERNEL_CS     (0x8)
15 %define KERNEL_DS     (0x10)
16 %define LOADER_CS     (0x18)
17 %define LOADER_DS     (0x20)
18
19 struc multiboot_module
20 mbm_mod_start:  resd    1
21 mbm_mod_end:    resd    1
22 mbm_string:     resd    1
23 mbm_reserved:   resd    1
24 endstruc
25
26 struc multiboot_address_range
27 mar_baselow:    resd 1
28 mar_basehigh:   resd 1
29 mar_lengthlow:  resd 1
30 mar_lengthhigh: resd 1
31 mar_type:       resd 1
32 mar_reserved:   resd 3
33 endstruc
34
35 ;
36 ; We are a .com program
37 ;
38 org 100h
39
40 ;
41 ; 16 bit code
42 ;
43 BITS 16
44
45 %define NDEBUG 1
46
47 %macro  DPRINT  1+
48 %ifndef NDEBUG
49         jmp     %%end_str
50
51 %%str:  db      %1
52
53 %%end_str:
54         push    di
55         push    ds
56         push    es
57         pop     ds
58         mov     di, %%str
59         call    print_string
60         pop     ds
61         pop     di
62 %endif
63 %endmacro
64
65 entry:
66         ;;
67         ;; Load stack
68         ;;
69         cli
70         push    ds
71         pop     ss
72         push    ds
73         pop     es
74         mov     sp, real_stack_end
75         sti
76
77         ;;
78         ;; Setup the 32-bit registers
79         ;;
80         mov     ebx, 0
81         mov     eax, 0
82         mov     ecx, 0
83         mov     edx, 0
84         mov     esi, 0
85         mov     edi, 0
86
87         ;;
88         ;; Set the position for the first module to be loaded
89         ;;
90         mov     dword [next_load_base], LOAD_BASE
91
92         ;;
93         ;; Setup various variables
94         ;;
95         mov     bx, ds
96         movzx   eax, bx
97         shl     eax, 4
98         add     [gdt_base], eax
99
100         ;;
101         ;; Setup the loader code and data segments
102         ;;
103         mov     eax, 0
104         mov     ax, cs
105         shl     eax, 4
106         mov     [_loader_code_base_0_15], ax
107         shr     eax, 16
108         mov     byte [_loader_code_base_16_23], al
109
110         mov     eax, 0
111         mov     ax, ds
112         shl     eax, 4
113         mov     [_loader_data_base_0_15], ax
114         shr     eax, 16
115         mov     byte [_loader_data_base_16_23], al
116
117         ;;
118         ;; load gdt
119         ;;
120         lgdt    [gdt_descr]
121
122         ;;
123         ;; Enable the A20 address line (to allow access to over 1mb)
124         ;;
125         call    empty_8042
126         mov     al, 0D1h                ; command write
127         out     064h, al
128         call    empty_8042
129         mov     al, 0DFh                ; A20 on
130         out     060h, al
131         call    empty_8042
132
133         ;;
134         ;; Make the argument list into a c string
135         ;;
136         mov     di, 081h
137         mov     si, dos_cmdline
138 .next_char
139         mov     al, [di]
140         mov     [si], al
141         cmp     byte [di], 0dh
142         je      .end_of_command_line
143         inc     di
144         inc     si
145         jmp     .next_char
146         
147 .end_of_command_line:
148         mov     byte [di], 0
149         mov     byte [si], 0
150         mov     [dos_cmdline_end], di
151         
152         ;;
153         ;; Make the argument list into a c string
154         ;;
155         mov     di, 081h
156 .next_char2
157         cmp     byte [di], 0
158         je      .end_of_command_line2
159         cmp     byte [di], ' '
160         jne     .not_space
161         mov     byte [di], 0
162 .not_space
163         inc     di
164         jmp     .next_char2
165 .end_of_command_line2
166
167         ;;
168         ;; Check if we want to skip the first character
169         ;;
170         cmp     byte [081h], 0
171         jne     .first_char_is_zero
172         mov     dx, 082h
173         jmp     .start_loading
174 .first_char_is_zero
175         mov     dx, 081h
176
177         ;;
178         ;; Check if we have reached the end of the string
179         ;;
180 .start_loading
181         mov     bx, dx
182         cmp     byte [bx], 0
183         jne     .more_modules
184         jmp     .done_loading
185
186 .more_modules
187         ;;
188         ;; Process the arguments
189         ;;
190         cmp     byte [di], '/'
191         jne     .no_next_module
192
193         mov     si, _multiboot_kernel_cmdline
194 .find_end:
195         cmp     byte [si], 0
196         je      .line_end
197         inc     si
198         jmp     .find_end
199
200 .line_end
201         mov     byte [si], ' '
202         inc     si
203 .line_copy
204         cmp     di, [dos_cmdline_end]
205         je      .done_copy
206         cmp     byte [di], 0
207         je      .done_copy
208         mov     al, byte [di]
209         mov     byte [si], al
210         inc     di
211         inc     si
212         jmp     .line_copy
213 .done_copy:
214         mov     byte [si], 0    
215         jmp     .next_module
216 .no_next_module:
217
218         ;;
219         ;; Display a message saying we are loading the module
220         ;;
221         mov     di, loading_msg
222         call    print_string
223         mov     di, dx
224         call    print_string
225
226         ;;
227         ;; Save the filename
228         ;;
229         mov     si, di
230         mov     edx, 0
231
232         mov     dx, [_multiboot_mods_count]
233         shl     dx, 8
234         add     dx, _multiboot_module_strings   
235         mov     bx, [_multiboot_mods_count]
236         imul    bx, bx, multiboot_module_size
237         add     bx, _multiboot_modules
238         mov     eax, 0
239         mov     ax, ds
240         shl     eax, 4
241         add     eax, edx
242         mov     [bx + mbm_string], eax
243         
244         mov     bx, dx
245 .copy_next_char
246         mov     al, [si]
247         mov     [bx], al
248         inc     si
249         inc     bx
250         cmp     al, 0
251         jne     .copy_next_char
252
253         ;;
254         ;; Load the file
255         ;;
256         push    di
257         mov     dx, di
258
259         ; Check if it is a symbol file
260         cmp     byte [bx-5],'.'
261         jne     .checkForHive
262         cmp     byte [bx-4],'s'
263         jne     .checkForHive
264         cmp     byte [bx-3],'y'
265         jne     .checkForHive
266         cmp     byte [bx-2],'m'
267         jne     .checkForHive
268
269         call    sym_load_module
270         jmp     .after_copy
271
272 .checkForHive:
273         ; Check if it is a symbol file
274         cmp     byte [bx-5],'.'
275         jne     .lst_copy
276         cmp     byte [bx-4],'h'
277         jne     .lst_copy
278         cmp     byte [bx-3],'i'
279         jne     .lst_copy
280         cmp     byte [bx-2],'v'
281         jne     .lst_copy
282
283         call    sym_load_module
284         jmp     .after_copy
285
286 .lst_copy:
287         ;; Check for a module list file
288         cmp     byte [bx-5],'.'
289         jne     .pe_copy
290         cmp     byte [bx-4],'l'
291         jne     .pe_copy
292         cmp     byte [bx-3],'s'
293         jne     .pe_copy
294         cmp     byte [bx-2],'t'
295         jne     .pe_copy
296
297         call    sym_load_module
298
299         push    es
300         mov     bx,0x9000
301         push    bx
302         pop     es
303         xor     edi,edi
304
305 .lst_copy_bytes:
306         mov     bx,_lst_name_local
307         
308 .lst_byte:
309         mov     al,[es:di]
310         inc     di
311         cmp     al,' '
312         jg      .lst_not_space
313         mov     byte [bx],0
314         inc     bx
315 .lst_space:
316         mov     al,[es:di]
317         inc     di
318         cmp     al,' '
319         jle     .lst_space
320 .lst_not_space:
321         cmp     al,'*'
322         je      .lst_end
323         mov     [bx],al
324         inc     bx
325         jmp     .lst_byte
326
327 .lst_end:
328         ;; We are here because the terminator was encountered
329         mov     byte [bx],0             ; Zero terminate
330         inc     bx
331         mov     byte [bx],0
332         mov     [dos_cmdline_end],bx    ; Put in cmd_line_length
333         mov     dx,_lst_name_local; Put this address in di
334         mov     di,dx                   ; This, too, at the start of the
335                                         ; string
336
337         pop     es
338
339         jmp     .start_loading  
340                         
341 .pe_copy:
342         call    pe_load_module
343
344 .after_copy:
345         pop     di
346         cmp     eax, 0
347         jne     .load_success
348         jmp     .exit
349 .load_success:
350         mov     ah, 02h
351         mov     dl, 0dh
352         int     021h
353         mov     ah, 02h
354         mov     dl, 0ah
355         int     021h
356
357         ;;
358         ;; Move onto the next module name in the command line
359         ;;
360 .next_module
361         cmp     di, [dos_cmdline_end]
362         je      .done_loading
363         cmp     byte [di], 0
364         je      .found_module_name
365         inc     di
366         jmp     .next_module
367 .found_module_name
368         inc     di
369         mov     dx, di
370         jmp     .start_loading
371
372 .done_loading
373
374         ;;
375         ;; Initialize the multiboot information
376         ;;
377         mov     eax, 0
378         mov     ax, ds
379         shl     eax, 4
380         
381         mov     [_multiboot_info_base], eax
382         add     dword [_multiboot_info_base], _multiboot_info
383         
384         mov     dword [_multiboot_flags], 0xc
385   
386         mov     [_multiboot_cmdline], eax
387         add     dword [_multiboot_cmdline], _multiboot_kernel_cmdline
388         
389         ;;
390         ;; Hide the kernel's entry in the list of modules
391         ;;
392         mov     [_multiboot_mods_addr], eax
393         mov     ebx, _multiboot_modules
394         add     ebx, multiboot_module_size
395         add     dword [_multiboot_mods_addr], ebx
396         dec     dword [_multiboot_mods_count]
397
398         ;;
399         ;; get extended memory size in KB
400         ;;
401         push    ebx
402         xor     ebx,ebx
403         mov     [_multiboot_mem_upper],ebx
404         mov     [_multiboot_mem_lower],ebx
405
406         mov     ax, 0xe801
407         int     015h
408         jc      .oldstylemem
409
410         cmp     ax, 0
411         je      .cmem
412
413         and     ebx, 0xffff
414         shl     ebx,6
415         mov     [_multiboot_mem_upper],ebx
416         and     eax,0xffff
417         add     dword [_multiboot_mem_upper],eax
418         jmp     .done_mem
419
420 .cmem:
421         cmp     cx, 0
422         je      .oldstylemem
423
424         and     edx, 0xFFFF
425         shl     edx, 6
426         mov     [_multiboot_mem_upper], edx
427         and     ecx, 0xFFFF
428         add     dword [_multiboot_mem_upper], ecx
429         jmp     .done_mem
430
431 .oldstylemem:
432         ;; int 15h opt e801 don't work , try int 15h, option 88h
433         mov     ah, 088h
434         int     015h
435         cmp     ax, 0
436         je      .cmosmem
437         mov     [_multiboot_mem_upper],ax
438         jmp     .done_mem
439 .cmosmem:
440         ;; int 15h opt 88h don't work , try read cmos
441         xor     eax,eax
442         mov     al, 0x31
443         out     0x70, al
444         in      al, 0x71
445         and     eax, 0xffff     ; clear carry
446         shl     eax,8
447         mov     [_multiboot_mem_upper],eax
448         xor     eax,eax
449         mov     al, 0x30
450         out     0x70, al
451         in      al, 0x71
452         and     eax, 0xffff     ; clear carry
453         add     [_multiboot_mem_lower],eax
454
455 .done_mem:
456
457         ;;
458         ;; Retrieve BIOS memory map if available
459         ;;
460         xor ebx,ebx
461         mov edi, _multiboot_address_ranges
462
463 .mmap_next:
464
465         mov edx, 'PAMS'
466         mov ecx, multiboot_address_range_size
467         mov eax, 0E820h
468         int 15h
469         jc  .done_mmap
470
471         cmp eax, 'PAMS'
472         jne .done_mmap
473
474         add edi, multiboot_address_range_size
475
476         cmp ebx, 0
477         jne .mmap_next
478
479         ;;
480         ;; Prepare multiboot memory map structures
481         ;;
482
483         ;; Fill in the address descriptor size field
484         mov dword [_multiboot_address_range_descriptor_size], multiboot_address_range_size
485
486         ;; Set flag and base address and length of memory map
487         or  dword [_multiboot_flags], 40h
488         mov eax, edi
489         sub eax, _multiboot_address_ranges
490         mov dword [_multiboot_mmap_length], eax
491
492         xor     eax, eax
493         mov     ax, ds
494         shl     eax, 4
495         mov     [_multiboot_mmap_addr], eax
496         add     dword [_multiboot_mmap_addr], _multiboot_address_ranges
497
498 .done_mmap:
499
500         pop ebx
501         
502         ;;
503         ;; Begin the pmode initalization
504         ;;
505         
506         ;;
507         ;; Save cursor position
508         ;;
509         mov     ax, 3           ;! Reset video mode
510         int     10h
511
512         mov     bl, 10
513         mov     ah, 12
514         int     10h
515
516         mov     ax, 1112h       ;! Use 8x8 font
517         xor     bl, bl
518         int     10h
519         mov     ax, 1200h       ;! Use alternate print screen
520         mov     bl, 20h
521         int     10h
522         mov     ah, 1h          ;! Define cursor (scan lines 6 to 7)
523         mov     cx, 0607h
524         int     10h
525
526         mov     ah, 1
527         mov     cx, 0600h
528         int     10h
529
530         mov     ah, 6           ; Scroll active page up
531         mov     al, 32h         ; Clear 50 lines
532         mov     cx, 0           ; Upper left of scroll
533         mov     dx, 314fh       ; Lower right of scroll
534         mov     bh, 1*10h+1     ; Use normal attribute on blanked lines
535         int     10h
536
537         mov     dx, 0
538         mov     dh, 0
539
540         mov     ah, 2
541         mov     bh, 0
542         int     10h
543
544         mov     dx, 0
545         mov     dh, 0
546
547         mov     ah, 2
548         mov     bh, 0
549         int     10h
550
551         mov     ah, 3
552         mov     bh, 0
553         int     10h
554         movzx   eax, dl
555 ;       mov     [_cursorx], eax
556         movzx   eax, dh
557 ;       mov     [_cursory], eax
558
559         cli
560
561         ;;
562         ;; Load the absolute address of the multiboot information structure
563         ;;
564         mov     ebx, [_multiboot_info_base]
565
566         ;;
567         ;; Enter pmode and clear prefetch queue
568         ;;
569         mov     eax,cr0
570         or      eax,0x10001
571         mov     cr0,eax
572         jmp     .next
573 .next:
574         ;;
575         ;; NOTE: This must be position independant (no references to
576         ;; non absolute variables)
577         ;;
578
579         ;;
580         ;; Initalize segment registers
581         ;;
582         mov     ax,KERNEL_DS
583         mov     ds,ax
584         mov     ss,ax
585         mov     es,ax
586         mov     fs,ax
587         mov     gs,ax
588
589         ;;
590         ;; Initalize eflags
591         ;;
592         push    dword 0
593         popf
594
595         ;;
596         ;; Load the multiboot magic value into eax
597         ;;      
598         mov     eax, 0x2badb002
599
600         ;;
601         ;; Jump to start of the kernel
602         ;;
603         jmp     dword KERNEL_CS:(LOAD_BASE+0x1000)
604
605         ;;
606         ;; Never get here
607         ;;
608
609 .exit:
610         mov     ax,04c00h
611         int     21h
612
613
614 ;
615 ; Print string in DS:DI
616 ;
617 print_string:
618         push    ebp
619         mov     bp, sp
620         push    eax
621         push    edx
622         push    edi
623
624         mov     ax, 0x0200
625 .loop:
626         mov     dl, [di]
627         cmp     dl, 0
628         je      .end_loop
629         cmp     dl, '%'
630         jne     .print_char
631         inc     di
632         mov     dl, [di]
633         cmp     dl, 'a'
634         jne     .not_ax
635         push    eax
636         mov     eax, [ss:bp - 4]
637         call    print_ax
638         pop     eax
639         jmp     .next_char
640
641 .not_ax:
642         cmp     dl, 'A'
643         jne     .not_eax
644         push    eax
645         mov     eax, [ss:bp - 4]
646         call    print_eax
647         pop     eax
648         jmp     .next_char
649
650 .not_eax:
651         cmp     dl, 'c'
652         jne     .not_cx
653         push    ax
654         mov     ax, cx
655         call    print_ax
656         pop     ax
657         jmp     .next_char
658
659 .not_cx:
660
661 .print_char:
662         int     0x21
663
664 .next_char:
665         inc     di
666         jmp     .loop
667
668 .end_loop:
669         pop     edi
670         pop     edx
671         pop     eax
672         pop     ebp
673         ret
674
675 ;
676 ; print_ax - print the number in the ax register
677 ;
678
679 print_ax:
680         push    ax
681         push    bx
682         push    cx
683         push    dx
684
685         mov     bx, ax
686         mov     ax, 0x0200
687         mov     cx, 4
688 .loop:
689         mov     dx, bx
690         shr     dx, 12
691         and     dl, 0x0f
692         cmp     dl, 0x0a
693         jge     .hex_val
694         add     dl, '0'
695         jmp     .not_hex
696
697 .hex_val:
698         add     dl, 'a' - 10
699
700 .not_hex:       
701         int     0x21
702         shl     bx, 4
703         dec     cx
704         jnz     .loop
705
706         pop     dx
707         pop     cx
708         pop     bx
709         pop     ax
710         ret
711
712 print_eax:
713         push    eax
714         push    ebx
715         push    ecx
716         push    edx
717
718         mov     ebx, eax
719         mov     ax, 0x0200
720         mov     cx, 8
721 .loop:
722         mov     edx, ebx
723         shr     edx, 28
724         and     dl, 0x0f
725         cmp     dl, 0x0a
726         jge     .hex_val
727         add     dl, '0'
728         jmp     .not_hex
729
730 .hex_val:
731         add     dl, 'a' - 10
732
733 .not_hex:
734         int     0x21
735         shl     ebx, 4
736         dec     cx
737         jnz     .loop
738
739         pop     edx
740         pop     ecx
741         pop     ebx
742         pop     eax
743         ret
744
745 STRUC   pe_doshdr
746 e_magic:        resw    1
747 e_cblp:         resw    1
748 e_cp:           resw    1
749 e_crlc:         resw    1
750 e_cparhdr:      resw    1
751 e_minalloc:     resw    1
752 e_maxalloc:     resw    1
753 e_ss:           resw    1
754 e_sp:           resw    1
755 e_csum:         resw    1
756 e_ip:           resw    1
757 e_cs:           resw    1
758 e_lfarlc:       resw    1
759 e_ovno:         resw    1
760 e_res:          resw    4
761 e_oemid:        resw    1
762 e_oeminfo:      resw    1
763 e_res2:         resw    10
764 e_lfanew:       resd    1
765 ENDSTRUC
766
767
768 _mb_magic:
769         dd 0
770 _mb_flags:
771         dd 0
772 _mb_checksum:
773         dd 0
774 _mb_header_addr:
775         dd 0
776 _mb_load_addr:
777         dd 0
778 _mb_load_end_addr:
779         dd 0
780 _mb_bss_end_addr:
781         dd 0
782 _mb_entry_addr:
783         dd 0
784
785 _cpe_doshdr:
786         times pe_doshdr_size db 0
787 _current_filehandle:
788         dw 0
789 _current_size:
790         dd 0
791 _current_file_size:
792         dd 0
793         
794 _lst_name_local:
795         times 2048 db 0
796         
797         ;;
798         ;; Load a SYM file
799         ;;      DS:DX = Filename
800         ;;
801 sym_load_module:
802         call    load_module1
803         call    load_module2
804         mov     edi, [next_load_base]
805         add     edi, [_current_file_size]
806
807         mov     eax, edi
808         test    di, 0xfff
809         jz      .sym_no_round
810         and     di, 0xf000
811         add     edi, 0x1000
812
813         ;;
814         ;; Clear unused space in the last page
815         ;;
816         mov     esi, edi
817         mov     ecx, edi
818         sub     ecx, eax
819
820 .sym_clear:
821         mov     byte [esi],0
822         inc     esi
823         loop    .sym_clear
824
825 .sym_no_round:
826
827         call    load_module3
828         ret
829
830         ;;
831         ;; Load a PE file
832         ;;      DS:DX = Filename
833         ;;
834 pe_load_module:
835         call    load_module1
836
837         ;;
838         ;; Read in the DOS EXE header
839         ;;
840         mov     ah, 0x3f
841         mov     bx, [_current_filehandle]
842         mov     cx, pe_doshdr_size
843         mov     dx, _cpe_doshdr
844         int     0x21
845         jnc     .header_read
846         mov     dx, error_file_read_failed
847         jmp     error
848 .header_read
849
850         ;;
851         ;; Check the DOS EXE magic
852         ;;
853         mov     ax, word [_cpe_doshdr + e_magic]
854         cmp     ax, 'MZ'
855         je      .mz_hdr_good
856         mov     dx, error_bad_mz
857         jmp     error
858 .mz_hdr_good
859
860         ;;
861         ;; Find the BSS size
862         ;;
863         mov     ebx, dword [_multiboot_mods_count]
864         cmp     ebx, 0
865         jne     .not_first
866         
867         mov     edx, 0
868         mov     ax, 0x4200
869         mov     cx, 0
870         mov     dx, 0x1004
871         mov     bx, [_current_filehandle]
872         int     0x21
873         jnc     .start_seek1
874         mov     dx, error_file_seek_failed
875         jmp     error
876 .start_seek1:
877         mov     ah, 0x3F
878         mov     bx, [_current_filehandle]
879         mov     cx, 32
880         mov     dx, _mb_magic
881         int     0x21
882         jnc     .mb_header_read
883         mov     dx, error_file_read_failed
884         jmp     error
885 .mb_header_read:
886         jmp     .first
887         
888 .not_first:
889         mov     dword [_mb_bss_end_addr], 0
890 .first:
891
892         call  load_module2
893         call  load_module3
894         ret
895
896 load_module1:
897         ;;
898         ;; Open file
899         ;;
900         mov     ax, 0x3d00
901         int     0x21
902         jnc     .file_opened
903         mov     dx, error_file_open_failed
904         jmp     error
905 .file_opened:
906
907         ;;
908         ;; Save the file handle
909         ;;
910         mov     [_current_filehandle], ax
911
912         ;;
913         ;; Print space
914         ;;
915         mov     ah,02h
916         mov     dl,' '
917         int     021h
918
919         ;;
920         ;; Seek to the start of the file
921         ;;
922         mov     ax, 0x4200
923         mov     bx, [_current_filehandle]
924         mov     cx, 0
925         mov     dx, 0
926         int     0x21
927         jnc     .seek_start
928         mov     dx, error_file_seek_failed
929         jmp     error
930 .seek_start:
931         ret
932
933 load_module2:
934         ;;
935         ;; Seek to the end of the file to get the file size
936         ;;
937         mov     edx, 0
938         mov     ax, 0x4202
939         mov     dx, 0
940         mov     cx, 0
941         mov     bx, [_current_filehandle]
942         int     0x21
943         jnc     .start_end
944         mov     dx, error_file_seek_failed
945         jmp     error
946 .start_end
947         shl     edx, 16
948         mov     dx, ax
949         mov     [_current_size], edx
950         mov     [_current_file_size], edx
951         
952         mov     edx, 0
953         mov     ax, 0x4200
954         mov     dx, 0
955         mov     cx, 0
956         mov     bx, [_current_filehandle]
957         int     0x21
958         jnc     .start_seek
959         mov     dx, error_file_seek_failed
960         jmp     error
961 .start_seek
962         
963         mov     edi, [next_load_base]
964         
965 .read_next:
966         cmp     dword [_current_size], 32768
967         jle     .read_tail
968
969         ;;
970         ;; Read in the file data
971         ;;
972         push    ds
973         mov     ah, 0x3f
974         mov     bx, [_current_filehandle]
975         mov     cx, 32768
976         mov     dx, 0x9000
977         mov     ds, dx
978         mov     dx, 0
979         int     0x21
980         jnc     .read_data_succeeded
981         pop     ds
982         mov     dx, error_file_read_failed
983         jmp     error
984 .read_data_succeeded:
985 %ifndef NDEBUG
986         mov     ah,02h
987         mov     dl,'#'
988         int     021h
989 %endif
990
991         ;;
992         ;; Copy the file data just read in to high memory
993         ;;
994         pop     ds
995         mov     esi, 0x90000
996         mov     ecx, 32768
997         call    _himem_copy
998 %ifndef NDEBUG
999         mov     ah,02h
1000         mov     dl,'$'
1001         int     021h
1002 %else
1003         mov     ah,02h
1004         mov     dl,'.'
1005         int     021h
1006 %endif
1007
1008         sub     dword [_current_size], 32768
1009         jmp     .read_next
1010
1011 .read_tail
1012         ;;
1013         ;; Read in the tailing part of the file data
1014         ;;
1015         push    ds
1016         mov     eax, [_current_size]
1017         mov     cx, ax
1018         mov     ah, 0x3f
1019         mov     bx, [_current_filehandle]
1020         mov     dx, 0x9000
1021         mov     ds, dx
1022         mov     dx, 0
1023         int     0x21
1024         jnc     .read_last_data_succeeded
1025         pop     ds
1026         mov     dx, error_file_read_failed
1027         jmp     error
1028 .read_last_data_succeeded:
1029         ;;
1030         ;; Close the file
1031         ;;
1032         mov     bx, [_current_filehandle]
1033         mov     ah, 0x3e
1034         int     0x21
1035 %ifndef NDEBUG
1036         mov     ah,02h
1037         mov     dl,'#'
1038         int     021h
1039 %endif
1040
1041         ;;
1042         ;; Copy the tailing part to high memory
1043         ;;
1044         pop     ds
1045         mov     ecx, [_current_size]
1046         mov     esi, 0x90000
1047         call    _himem_copy
1048 %ifndef NDEBUG
1049         mov     ah,02h
1050         mov     dl,'$'
1051         int     021h
1052 %else
1053         mov     ah,02h
1054         mov     dl,'.'
1055         int     021h
1056 %endif
1057
1058         mov     edx, [_mb_bss_end_addr]
1059         cmp     edx, 0
1060         je      .no_bss
1061         mov     edi, edx        
1062 .no_bss:                
1063         test    di, 0xfff
1064         jz      .no_round
1065         and     di, 0xf000
1066         add     edi, 0x1000
1067 .no_round:
1068         ret
1069
1070 load_module3:  
1071         mov     bx, [_multiboot_mods_count]
1072         imul    bx, bx, multiboot_module_size
1073         add     bx, _multiboot_modules
1074         
1075         mov     edx, [next_load_base]
1076         mov     [bx + mbm_mod_start], edx
1077         mov     [bx + mbm_mod_end], edi
1078         mov     [next_load_base], edi
1079         mov     dword [bx + mbm_reserved], 0
1080         
1081         inc     dword [_multiboot_mods_count]
1082
1083         mov     eax, 1
1084         
1085         ret
1086
1087         ;;
1088         ;; On error print a message and return zero
1089         ;;
1090 error:
1091         mov     ah, 0x9
1092         int     0x21
1093         mov     eax, 0
1094         ret
1095
1096         ;;
1097         ;; Copy to high memory
1098         ;; ARGUMENTS
1099         ;;      ESI = Source address
1100         ;;      EDI = Destination address
1101         ;;      ECX = Byte count
1102         ;; RETURNS
1103         ;;      EDI = End of the destination region
1104         ;;      ECX = 0
1105         ;; 
1106 _himem_copy:
1107         push    ds              ; Save DS
1108         push    es              ; Save ES
1109         push    eax
1110         push    esi
1111
1112         cmp     eax, 0
1113         je      .l3
1114         
1115         cli                     ; No interrupts during pmode
1116         
1117         mov     eax, cr0        ; Entered protected mode
1118         or      eax, 0x1
1119         mov     cr0, eax
1120
1121         jmp     .l1             ; Flush prefetch queue
1122 .l1:
1123         
1124         mov     eax, KERNEL_DS  ; Load DS with a suitable selector
1125         mov     ds, ax
1126         mov     eax, KERNEL_DS
1127         mov     es, ax
1128
1129         cld
1130         a32 rep movsb
1131 ;.l2:
1132 ;       mov     al, [esi]       ; Copy the data
1133 ;       mov     [edi], al
1134 ;       dec     ecx
1135 ;       inc     esi
1136 ;       inc     edi
1137 ;       cmp     ecx, 0
1138 ;       jne     .l2
1139
1140         mov     eax, cr0        ; Leave protected mode
1141         and     eax, 0xfffffffe
1142         mov     cr0, eax
1143         
1144         jmp     .l3
1145 .l3:    
1146         sti
1147         pop     esi
1148         pop     eax
1149         pop     es
1150         pop     ds
1151         ret
1152
1153 ;
1154 ; Loading message
1155 ;
1156 loading_msg     db      'Loading: ',0
1157
1158 ;;
1159 ;; Next free address in high memory
1160 ;;
1161 next_load_base dd 0
1162
1163 ;
1164 ; Needed for enabling the a20 address line
1165 ;
1166 empty_8042:
1167         jmp     empty_8042_1
1168 empty_8042_1:
1169         jmp     empty_8042_2
1170 empty_8042_2:   
1171         in      al,064h
1172         test    al,02h
1173         jnz     empty_8042
1174         ret
1175
1176 ;
1177 ; GDT descriptor
1178 ;
1179 align 8
1180 gdt_descr:
1181 gdt_limit:
1182         dw      (5*8)-1
1183 gdt_base:
1184         dd      _gdt
1185
1186         ;;
1187         ;; Our initial stack
1188         ;;
1189 real_stack times 1024 db 0
1190 real_stack_end:
1191
1192         ;;
1193         ;; DOS commandline buffer
1194         ;;
1195 dos_cmdline times 256 db 0
1196 dos_cmdline_end dw 0
1197
1198         ;;
1199         ;; Boot information structure
1200         ;;
1201 _multiboot_info_base:
1202         dd      0x0
1203
1204 _multiboot_info:
1205 _multiboot_flags:
1206         dd      0x0
1207 _multiboot_mem_lower:
1208         dd      0x0
1209 _multiboot_mem_upper:
1210         dd      0x0
1211 _multiboot_boot_device:
1212         dd      0x0
1213 _multiboot_cmdline:     
1214         dd      0x0
1215 _multiboot_mods_count:
1216         dd      0x0
1217 _multiboot_mods_addr:
1218         dd      0x0
1219 _multiboot_syms:
1220         times 12 db 0
1221 _multiboot_mmap_length:
1222         dd      0x0
1223 _multiboot_mmap_addr:
1224         dd      0x0
1225 _multiboot_drives_count:
1226         dd      0x0
1227 _multiboot_drives_addr:
1228         dd      0x0
1229 _multiboot_config_table:
1230         dd      0x0
1231 _multiboot_boot_loader_name:
1232         dd      0x0
1233 _multiboot_apm_table:
1234         dd      0x0
1235
1236 _multiboot_modules:     
1237         times (64*multiboot_module_size) db 0
1238 _multiboot_module_strings:
1239         times (64*256) db 0
1240
1241 _multiboot_address_range_descriptor_size dd 0
1242
1243 _multiboot_address_ranges:
1244         times (64*multiboot_address_range_size) db 0
1245
1246 _multiboot_kernel_cmdline:
1247         db 'multi(0)disk(0)rdisk(0)partition(1)\reactos'
1248         times 255-($-_multiboot_kernel_cmdline) db 0
1249
1250         ;;
1251         ;; Global descriptor table
1252         ;;
1253 _gdt:   
1254         dw      0x0             ; Zero descriptor
1255         dw      0x0
1256         dw      0x0
1257         dw      0x0
1258
1259         dw      0xffff          ; Kernel code descriptor
1260         dw      0x0000
1261         dw      0x9a00
1262         dw      0x00cf
1263
1264         dw      0xffff          ;  Kernel data descriptor
1265         dw      0x0000
1266         dw      0x9200
1267         dw      0x00cf
1268
1269         dw      0xffff          ;  Loader code descriptor
1270 _loader_code_base_0_15:
1271         dw      0x0000
1272 _loader_code_base_16_23:
1273         db      0x00
1274         db      0x9a
1275         dw      0x0000
1276         
1277         dw      0xffff          ;  Loader data descriptor
1278 _loader_data_base_0_15:
1279         dw      0x0000
1280 _loader_data_base_16_23:
1281         db      0x00
1282         db      0x92
1283         dw      0x0000
1284
1285 error_pmode_already:
1286         db      'Error: The processor is already in protected mode'
1287         db      0xa, 0xd, '$'
1288 error_file_open_failed:
1289         db      'Error: Failed to open file'
1290         db      0xa, 0xd, '$'
1291 error_file_seek_failed:
1292         db      'Error: File seek failed'
1293         db      0xa, 0xd, '$'
1294 error_file_read_failed:
1295         db      'Error: File read failed'
1296         db      0xa, 0xd, '$'
1297 error_coff_load_failed:
1298         db      'Error: Failed to load COFF file'
1299         db      0xa, 0xd, '$'
1300 error_bad_mz:
1301         db      'Error: Bad DOS EXE magic'
1302         db      0xa, 0xd, '$'