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