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