Merge branch 'master', remote branch 'origin' into chouffe
[profile/ivi/syslinux.git] / core / ldlinux.asm
1 ; -*- fundamental -*- (asm-mode sucks)
2 ; ****************************************************************************
3 ;
4 ;  ldlinux.asm
5 ;
6 ;  A program to boot Linux kernels off an MS-DOS formatted floppy disk.  This
7 ;  functionality is good to have for installation floppies, where it may
8 ;  be hard to find a functional Linux system to run LILO off.
9 ;
10 ;  This program allows manipulation of the disk to take place entirely
11 ;  from MS-LOSS, and can be especially useful in conjunction with the
12 ;  umsdos filesystem.
13 ;
14 ;   Copyright 1994-2009 H. Peter Anvin - All Rights Reserved
15 ;   Copyright 2009 Intel Corporation; author: H. Peter Anvin
16 ;
17 ;  This program is free software; you can redistribute it and/or modify
18 ;  it under the terms of the GNU General Public License as published by
19 ;  the Free Software Foundation, Inc., 53 Temple Place Ste 330,
20 ;  Boston MA 02111-1307, USA; either version 2 of the License, or
21 ;  (at your option) any later version; incorporated herein by reference.
22 ;
23 ; ****************************************************************************
24
25 %ifndef IS_MDSLINUX
26 %define IS_SYSLINUX 1
27 %endif
28 %include "head.inc"
29
30 ;
31 ; Some semi-configurable constants... change on your own risk.
32 ;
33 my_id           equ syslinux_id
34 FILENAME_MAX_LG2 equ 6                  ; log2(Max filename size Including final null)
35 FILENAME_MAX    equ (1<<FILENAME_MAX_LG2) ; Max mangled filename size
36 NULLFILE        equ 0                   ; First char space == null filename
37 NULLOFFSET      equ 0                   ; Position in which to look
38 retry_count     equ 16                  ; How patient are we with the disk?
39 %assign HIGHMEM_SLOP 0                  ; Avoid this much memory near the top
40 LDLINUX_MAGIC   equ 0x3eb202fe          ; A random number to identify ourselves with
41
42 MAX_OPEN_LG2    equ 6                   ; log2(Max number of open files)
43 MAX_OPEN        equ (1 << MAX_OPEN_LG2)
44
45 SECTOR_SHIFT    equ 9
46 SECTOR_SIZE     equ (1 << SECTOR_SHIFT)
47
48 DIRENT_SHIFT    equ 5
49 DIRENT_SIZE     equ (1 << DIRENT_SHIFT)
50
51 ROOT_DIR_WORD   equ 0x002F
52
53 ;
54 ; The following structure is used for "virtual kernels"; i.e. LILO-style
55 ; option labels.  The options we permit here are `kernel' and `append
56 ; Since there is no room in the bottom 64K for all of these, we
57 ; stick them in high memory and copy them down before we need them.
58 ;
59                 struc vkernel
60 vk_vname:       resb FILENAME_MAX       ; Virtual name **MUST BE FIRST!**
61 vk_rname:       resb FILENAME_MAX       ; Real name
62 vk_appendlen:   resw 1
63 vk_type:        resb 1                  ; Type of file
64                 alignb 4
65 vk_append:      resb max_cmd_len+1      ; Command line
66                 alignb 4
67 vk_end:         equ $                   ; Should be <= vk_size
68                 endstruc
69
70 ;
71 ; File structure.  This holds the information for each currently open file.
72 ;
73                 struc open_file_t
74 file_sector     resd 1                  ; Sector pointer (0 = structure free)
75 file_bytesleft  resd 1                  ; Number of bytes left
76 file_left       resd 1                  ; Number of sectors left
77                 resd 1                  ; Unused
78                 endstruc
79
80 ;
81 ; Structure for codepage files
82 ;
83                 struc cp
84 .magic          resd 2                  ; 8-byte magic number
85 .reserved       resd 6                  ; Reserved for future use
86 .uppercase      resb 256                ; Internal upper-case table
87 .unicode        resw 256                ; Unicode matching table
88 .unicode_alt    resw 256                ; Alternate Unicode matching table
89                 endstruc
90
91 %ifndef DEPEND
92 %if (open_file_t_size & (open_file_t_size-1))
93 %error "open_file_t is not a power of 2"
94 %endif
95 %endif
96
97 ; ---------------------------------------------------------------------------
98 ;   BEGIN CODE
99 ; ---------------------------------------------------------------------------
100
101 ;
102 ; Memory below this point is reserved for the BIOS and the MBR
103 ;
104                 section .earlybss
105 trackbufsize    equ 8192
106 trackbuf        resb trackbufsize       ; Track buffer goes here
107                 ; ends at 2800h
108
109                 section .bss
110                 alignb 4
111 FAT             resd 1                  ; Location of (first) FAT
112 RootDirArea     resd 1                  ; Location of root directory area
113 RootDir         resd 1                  ; Location of root directory proper
114 DataArea        resd 1                  ; Location of data area
115 RootDirSize     resd 1                  ; Root dir size in sectors
116 TotalSectors    resd 1                  ; Total number of sectors
117 ClustSize       resd 1                  ; Bytes/cluster
118 ClustMask       resd 1                  ; Sectors/cluster - 1
119 Clusters        resd 1                  ; Total number of clusters
120 CopySuper       resb 1                  ; Distinguish .bs versus .bss
121 DriveNumber     resb 1                  ; BIOS drive number
122 ClustShift      resb 1                  ; Shift count for sectors/cluster
123 ClustByteShift  resb 1                  ; Shift count for bytes/cluster
124
125                 alignb open_file_t_size
126 Files           resb MAX_OPEN*open_file_t_size
127
128 ;
129 ; Common bootstrap code for disk-based derivatives
130 ;
131 %include "diskstart.inc"
132
133 ;
134 ; Compute some information about this filesystem.
135 ;
136
137 ; First, generate the map of regions
138 genfatinfo:
139                 mov edx,[bxSectors]
140                 and dx,dx
141                 jnz .have_secs
142                 mov edx,[bsHugeSectors]
143 .have_secs:
144                 mov [TotalSectors],edx
145
146                 mov eax,[bxResSectors]
147                 mov [FAT],eax                   ; Beginning of FAT
148                 mov edx,[bxFATsecs]
149                 and dx,dx
150                 jnz .have_fatsecs
151                 mov edx,[bootsec+36]            ; FAT32 BPB_FATsz32
152 .have_fatsecs:
153                 imul edx,[bxFATs]
154                 add eax,edx
155                 mov [RootDirArea],eax           ; Beginning of root directory
156                 mov [RootDir],eax               ; For FAT12/16 == root dir location
157
158                 mov edx,[bxRootDirEnts]
159                 add dx,SECTOR_SIZE/32-1
160                 shr dx,SECTOR_SHIFT-5
161                 mov [RootDirSize],edx
162                 add eax,edx
163                 mov [DataArea],eax              ; Beginning of data area
164
165 ; Next, generate a cluster size shift count and mask
166                 mov eax,[bxSecPerClust]
167                 bsr cx,ax
168                 mov [ClustShift],cl
169                 push cx
170                 add cl,SECTOR_SHIFT
171                 mov [ClustByteShift],cl
172                 pop cx
173                 dec ax
174                 mov [ClustMask],eax
175                 inc ax
176                 shl eax,SECTOR_SHIFT
177                 mov [ClustSize],eax
178
179 ;
180 ; FAT12, FAT16 or FAT28^H^H32?  This computation is fscking ridiculous.
181 ;
182 getfattype:
183                 mov eax,[TotalSectors]
184                 sub eax,[DataArea]
185                 shr eax,cl                      ; cl == ClustShift
186                 mov cl,nextcluster_fat12-(nextcluster+2)
187                 cmp eax,0xFF4                   ; FAT12 limit
188                 jbe .setsize
189                 mov cl,nextcluster_fat16-(nextcluster+2)
190                 cmp eax,0xFFF4                  ; FAT16 limit
191                 jbe .setsize
192                 ;
193                 ; FAT32, root directory is a cluster chain
194                 ;
195                 mov ecx,0x0FFFFFF4              ; Max possible cluster count
196                 cmp eax,ecx
197                 jb .oksize
198                 mov eax,ecx
199 .oksize:
200
201                 mov cl,[ClustShift]
202                 mov edx,[bootsec+44]            ; Root directory cluster
203                 sub edx,2
204                 shl edx,cl
205                 add edx,[DataArea]
206                 mov [RootDir],edx
207                 mov cl,nextcluster_fat28-(nextcluster+2)
208                 mov byte [SuperSize],superblock_len_fat32
209 .setsize:
210                 mov byte [nextcluster+1],cl
211                 mov [Clusters],eax              ; Total clusters
212
213 ;
214 ; Common initialization code
215 ;
216 %include "cpuinit.inc"
217 %include "init.inc"
218
219 ;
220 ; Initialize the metadata cache
221 ;
222                 call initcache
223
224 ;
225 ; Now, everything is "up and running"... patch kaboom for more
226 ; verbosity and using the full screen system
227 ;
228                 ; E9 = JMP NEAR
229                 mov dword [kaboom.patch],0e9h+((kaboom2-(kaboom.patch+3)) << 8)
230
231 ;
232 ; Now we're all set to start with our *real* business.  First load the
233 ; configuration file (if any) and parse it.
234 ;
235 ; In previous versions I avoided using 32-bit registers because of a
236 ; rumour some BIOSes clobbered the upper half of 32-bit registers at
237 ; random.  I figure, though, that if there are any of those still left
238 ; they probably won't be trying to install Linux on them...
239 ;
240 ; The code is still ripe with 16-bitisms, though.  Not worth the hassle
241 ; to take'm out.  In fact, we may want to put them back if we're going
242 ; to boot ELKS at some point.
243 ;
244
245 ;
246 ; Load configuration file
247 ;
248                 mov si,config_name      ; Save configuration file name
249                 mov di,ConfigName
250                 call strcpy
251                 mov word [CurrentDirName],ROOT_DIR_WORD ; Write '/',0 to the CurrentDirName
252
253                 mov eax,[RootDir]       ; Make the root directory ...
254                 mov [CurrentDir],eax    ; ... the current directory
255                 mov di,syslinux_cfg1
256                 push di
257                 call open
258                 pop di
259                 jnz .config_open
260                 mov di,syslinux_cfg2
261                 push di
262                 call open
263                 pop di
264                 jnz .config_open
265                 mov di,syslinux_cfg3
266                 push di
267                 call open
268                 pop di
269                 jz no_config_file
270 .config_open:
271                 push si
272                 mov si,di
273                 push si
274                 mov di,CurrentDirName
275                         ; This is inefficient as it will copy more than needed
276                         ;   but not by too much
277                 call strcpy
278                 mov ax,config_name      ;Cut it down
279                 pop si
280                 sub ax,si
281                 mov di,CurrentDirName
282                 add di,ax
283                 mov byte [di],0
284                 pop si
285                 mov eax,[PrevDir]       ; Make the directory with syslinux.cfg ...
286                 mov [CurrentDir],eax    ; ... the current directory
287
288 ;
289 ; Now we have the config file open.  Parse the config file and
290 ; run the user interface.
291 ;
292 %include "ui.inc"
293
294 ;
295 ; allocate_file: Allocate a file structure
296 ;
297 ;               If successful:
298 ;                 ZF set
299 ;                 BX = file pointer
300 ;               In unsuccessful:
301 ;                 ZF clear
302 ;
303 allocate_file:
304                 TRACER 'a'
305                 push cx
306                 mov bx,Files
307                 mov cx,MAX_OPEN
308 .check:         cmp dword [bx], byte 0
309                 je .found
310                 add bx,open_file_t_size         ; ZF = 0
311                 loop .check
312                 ; ZF = 0 if we fell out of the loop
313 .found:         pop cx
314                 ret
315
316 ;
317 ; alloc_fill_dir:
318 ;       Allocate then fill a file structure for a directory starting in
319 ;       sector EAX.
320 ;
321 ;       Assumes DS == ES == CS.
322 ;
323 ;            If successful:
324 ;               ZF clear
325 ;               SI      = file pointer
326 ;            If unsuccessful
327 ;               ZF set
328 ;               EAX clobbered
329 ;
330 alloc_fill_dir:
331                 push bx
332                 call allocate_file
333                 jnz .alloc_failure
334 .found:
335                 mov si,bx
336                 mov [si+file_sector],eax        ; Current sector
337                 mov dword [si+file_bytesleft],0 ; Current offset
338                 mov [si+file_left],eax          ; Beginning sector
339                 pop bx
340                 ret
341
342 .alloc_failure:
343                 pop bx
344                 xor eax,eax                     ; ZF <- 1
345                 ret
346
347 ;
348 ; search_dos_dir:
349 ;            Search a specific directory for a pre-mangled filename in
350 ;            MangledBuf, in the directory starting in sector EAX.
351 ;
352 ;            NOTE: This file considers finding a zero-length file an
353 ;            error.  This is so we don't have to deal with that special
354 ;            case elsewhere in the program (most loops have the test
355 ;            at the end).
356 ;
357 ;            Assumes DS == ES == CS.
358 ;
359 ;            If successful:
360 ;               ZF clear
361 ;               SI      = file pointer
362 ;               EAX     = file length (MAY BE ZERO!)
363 ;               DL      = file attribute
364 ;               DH      = clobbered
365 ;            If unsuccessful
366 ;               ZF set
367 ;               EAX, SI, DX clobbered
368 ;
369
370 search_dos_dir:
371                 push bx
372                 call allocate_file
373                 jnz .alloc_failure
374
375                 push cx
376                 push gs
377                 push es
378                 push ds
379                 pop es                          ; ES = DS
380
381                 ; Compute the value of a possible VFAT longname
382                 ; "last" entry (which, of course, comes first...)
383                 push ax
384                 push dx
385                 mov ax,[NameLen]
386                 add ax,12
387                 xor dx,dx
388                 mov cx,13
389                 div cx
390                 or al,40h
391                 mov [VFATInit],al
392                 mov [VFATNext],al
393                 pop dx
394                 pop ax
395
396 .scansector:
397                 ; EAX <- directory sector to scan
398                 call getcachesector
399                 ; GS:SI now points to this sector
400
401                 mov cx,SECTOR_SIZE/32           ; 32 == directory entry size
402 .scanentry:
403                 cmp byte [gs:si],0
404                 jz .failure                     ; Hit directory high water mark
405                 cmp word [gs:si+11],0Fh         ; Long filename
406                 jne .short_entry
407
408                 ; Process a VFAT long entry
409                 pusha
410                 mov al,[gs:si]
411                 cmp al,[VFATNext]
412                 jne .not_us
413                 mov bl,[gs:si+13]
414                 test al,40h
415                 jz .match_csum
416                 ; Get the initial checksum value
417                 mov [VFATCsum],bl
418                 jmp .done_csum
419 .match_csum:
420                 cmp bl,[VFATCsum]
421                 jne .not_us                     ; Checksum mismatch
422 .done_csum:
423                 and ax,03fh
424                 jz .not_us                      ; Can't be zero...
425                 dec ax
426                 mov [VFATNext],al               ; Optimistically...
427                 mov bx,ax
428                 shl bx,2                        ; *4
429                 add ax,bx                       ; *5
430                 add bx,bx                       ; *8
431                 add bx,ax                       ; *13
432                 cmp bx,[NameLen]
433                 jae .not_us
434                 mov di,[NameStart]
435                 inc si
436                 mov cx,13
437 .vfat_cmp:
438                 gs lodsw
439                 push bx
440                 cmp bx,[NameLen]
441                 jae .vfat_tail
442                 movzx bx,byte [bx+di]
443                 add bx,bx
444                 cmp ax,[cp_unicode+bx]          ; Primary case
445                 je .ucs_ok
446                 cmp ax,[cp_unicode_alt+bx]      ; Alternate case
447                 je .ucs_ok
448                 ; Mismatch...
449                 jmp .not_us_pop
450 .vfat_tail:
451                 ; *AT* the end we should have 0x0000, *AFTER* the end
452                 ; we should have 0xFFFF...
453                 je .vfat_end
454                 inc ax                  ; 0xFFFF -> 0x0000
455 .vfat_end:
456                 and ax,ax
457                 jnz .not_us_pop
458 .ucs_ok:
459                 pop bx
460                 inc bx
461                 cmp cx,3
462                 je .vfat_adj_add2
463                 cmp cx,9
464                 jne .vfat_adj_add0
465 .vfat_adj_add3: inc si
466 .vfat_adj_add2: inc si
467 .vfat_adj_add1: inc si
468 .vfat_adj_add0:
469                 loop .vfat_cmp
470                 ; Okay, if we got here we had a match on this particular
471                 ; entry... live to see another one.
472                 popa
473                 jmp .next_entry
474
475 .not_us_pop:
476                 pop bx
477 .not_us:
478                 popa
479                 jmp .nomatch
480
481 .short_entry:
482                 test byte [gs:si+11],8          ; Ignore volume labels
483                 jnz .nomatch
484
485                 cmp byte [VFATNext],0           ; Do we have a longname match?
486                 jne .no_long_match
487
488                 ; We already have a VFAT longname match, however,
489                 ; the match is only valid if the checksum matches
490                 push cx
491                 push si
492                 push ax
493                 xor ax,ax
494                 mov cx,11
495 .csum_loop:
496                 gs lodsb
497                 ror ah,1
498                 add ah,al
499                 loop .csum_loop
500                 cmp ah,[VFATCsum]
501                 pop ax
502                 pop si
503                 pop cx
504                 je .found                       ; Got a match on longname
505
506 .no_long_match:                                 ; Look for a shortname match
507                 push cx
508                 push si
509                 push di
510                 mov di,MangledBuf
511                 mov cx,11
512                 gs repe cmpsb
513                 pop di
514                 pop si
515                 pop cx
516                 je .found
517 .nomatch:
518                 ; Reset the VFAT matching state machine
519                 mov dh,[VFATInit]
520                 mov [VFATNext],dh
521 .next_entry:
522                 add si,32
523                 dec cx
524                 jnz .scanentry
525
526                 call nextsector
527                 jnc .scansector                 ; CF is set if we're at end
528
529                 ; If we get here, we failed
530 .failure:
531                 pop es
532                 pop gs
533                 pop cx
534 .alloc_failure:
535                 pop bx
536                 xor eax,eax                     ; ZF <- 1
537                 ret
538 .found:
539                 mov eax,[gs:si+28]              ; File size
540                 add eax,SECTOR_SIZE-1
541                 shr eax,SECTOR_SHIFT
542                 mov [bx+4],eax                  ; Sector count
543
544                 mov cl,[ClustShift]
545                 mov dx,[gs:si+20]               ; High cluster word
546                 shl edx,16
547                 mov dx,[gs:si+26]               ; Low cluster word
548                 sub edx,2
549                 shl edx,cl
550                 add edx,[DataArea]
551                 mov [bx],edx                    ; Starting sector
552
553                 mov eax,[gs:si+28]              ; File length again
554                 mov dl,[gs:si+11]               ; File attribute
555                 mov si,bx                       ; File pointer...
556                 and si,si                       ; ZF <- 0
557
558                 pop es
559                 pop gs
560                 pop cx
561                 pop bx
562                 ret
563
564                 section .data
565                 alignz 4
566                 ; Note: we have no use of the first 32 bytes (header),
567                 ; nor of the folloing 32 bytes (case mapping of control
568                 ; characters), as long as we adjust the offsets appropriately.
569 codepage        equ $-(32+32)
570 codepage_data:  incbin "codepage.cp",32+32
571 cp_uppercase    equ     codepage+cp.uppercase
572 cp_unicode      equ     codepage+cp.unicode
573 cp_unicode_alt  equ     codepage+cp.unicode_alt
574 codepage_end    equ $
575
576                 section .text
577 ;
578 ; Input:  UCS-2 character in AX
579 ; Output: Single byte character in AL, ZF = 1
580 ;         On failure, returns ZF = 0
581 ;
582 ucs2_to_cp:
583                 push es
584                 push di
585                 push cx
586                 push cs
587                 pop es
588                 mov di,cp_unicode
589                 mov cx,512
590                 repne scasw
591                 xchg ax,cx
592                 pop cx
593                 pop di
594                 pop es
595                 not ax          ; Doesn't change the flags!
596                 ret
597
598                 section .bss
599 VFATInit        resb 1
600 VFATNext        resb 1
601 VFATCsum        resb 1
602
603                 section .text
604 ;
605 ; close_file:
606 ;            Deallocates a file structure (pointer in SI)
607 ;            Assumes CS == DS.
608 ;
609 close_file:
610                 and si,si
611                 jz .closed
612                 mov dword [si],0                ; First dword == file_sector
613                 xor si,si
614 .closed:        ret
615
616 ;
617 ; close_dir:
618 ;            Deallocates a directory structure (pointer in SI)
619 ;            Assumes CS == DS.
620 ;
621 close_dir:
622                 and si,si
623                 jz .closed
624                 mov dword [si],0                ; First dword == file_sector
625                 xor si,si
626 .closed:        ret
627
628 ;
629 ; searchdir:
630 ;
631 ;       Open a file
632 ;
633 ;            On entry:
634 ;               DS:DI   = filename
635 ;            If successful:
636 ;               ZF clear
637 ;               SI              = file pointer
638 ;               EAX             = file length in bytes
639 ;            If unsuccessful
640 ;               ZF set
641 ;
642 ; Assumes CS == DS == ES, and trashes BX and CX.
643 ;
644 searchdir:
645                 mov eax,[CurrentDir]
646                 cmp byte [di],'/'       ; Root directory?
647                 jne .notroot
648                 mov eax,[RootDir]
649                 inc di
650 .notroot:
651
652 .pathwalk:
653                 push eax                ; <A> Current directory sector
654                 mov si,di
655 .findend:
656                 lodsb
657                 cmp al,' '
658                 jbe .endpath
659                 cmp al,'/'
660                 jne .findend
661 .endpath:
662                 xchg si,di              ; GRC: si begin; di end[ /]+1
663                 pop eax                 ; <A> Current directory sector
664
665                         ; GRC Here I need to check if di-1 = si which signifies
666                         ;       we have the desired directory in EAX
667                         ; What about where the file name = "."; later
668                 mov dx,di
669                 dec dx
670                 cmp dx,si
671                 jz .founddir
672
673                 mov [PrevDir],eax       ; Remember last directory searched
674
675                 push di
676                 call mangle_dos_name    ; MangledBuf <- component
677                 call search_dos_dir
678                 pop di
679                 jz .notfound            ; Pathname component missing
680
681                 cmp byte [di-1],'/'     ; Do we expect a directory
682                 je .isdir
683
684                 ; Otherwise, it should be a file
685 .isfile:
686                 test dl,18h             ; Subdirectory|Volume Label
687                 jnz .badfile            ; If not a file, it's a bad thing
688
689                 ; SI and EAX are already set
690                 mov [si+file_bytesleft],eax
691                 push eax
692                 add eax,SECTOR_SIZE-1
693                 shr eax,SECTOR_SHIFT
694                 mov [si+file_left],eax  ; Sectors left
695                 pop eax
696                 and eax,eax             ; EAX != 0
697                 jz .badfile
698                 ret                     ; Done!
699
700                 ; If we expected a directory, it better be one...
701 .isdir:
702                 test dl,10h             ; Subdirectory
703                 jz .badfile
704
705                 xor eax,eax
706                 xchg eax,[si+file_sector] ; Get sector number and free file structure
707                 jmp .pathwalk           ; Walk the next bit of the path
708
709                 ; Found the desired directory; ZF set but EAX not 0
710 .founddir:
711                 ret
712
713 .badfile:
714                 xor eax,eax
715                 mov [si],eax            ; Free file structure
716
717 .notfound:
718                 xor eax,eax             ; Zero out EAX
719                 ret
720
721 ;
722 ; readdir: Read one file from a directory
723 ;
724 ;       ES:DI   -> String buffer (filename)
725 ;       DS:SI   -> Pointer to open_file_t
726 ;       DS      Must be the SYSLINUX Data Segment
727 ;
728 ;       Returns the file's name in the filename string buffer
729 ;       EAX returns the file size
730 ;       EBX returns the beginning sector (currently without offsetting)
731 ;       DL returns the file type
732 ;       The directory handle's data is incremented to reflect a name read.
733 ;
734 readdir:
735                 push ecx
736                 push bp         ; Using bp to transfer between segment registers
737                 push si
738                 push es
739                 push fs         ; Using fs to store the current es (from COMBOOT)
740                 push gs
741                 mov bp,es
742                 mov fs,bp
743                 cmp si,0
744                 jz .fail
745 .load_handle:
746                 mov eax,[ds:si+file_sector]     ; Current sector
747                 mov ebx,[ds:si+file_bytesleft]  ; Current offset
748                 cmp eax,0
749                 jz .fail
750 .fetch_cache:
751                 call getcachesector
752 .move_current:
753                 add si,bx       ; Resume last position in sector
754                 mov ecx,SECTOR_SIZE     ; 0 out high part
755                 sub cx,bx
756                 shr cx,5        ; Number of entries left
757 .scanentry:
758                 cmp byte [gs:si],0
759                 jz .fail
760                 cmp word [gs:si+11],0Fh         ; Long filename
761                 jne .short_entry
762
763 .vfat_entry:
764                 push eax
765                 push ecx
766                 push si
767                 push di
768 .vfat_ln_info:          ; Get info about the line that we're on
769                 mov al,[gs:si]
770                 test al,40h
771                 jz .vfat_tail_ln
772                 and al,03Fh
773                 mov ah,1        ; On beginning line
774                 jmp .vfat_ck_ln
775
776 .vfat_tail_ln:  ; VFAT tail line processing (later in VFAT, head in name)
777                 test al,80h     ; Invalid data?
778                 jnz .vfat_abort
779                 mov ah,0        ; Not on beginning line
780                 cmp dl,al
781                 jne .vfat_abort ; Is this the entry we need?
782                 mov bl,[gs:si+13]
783                 cmp bl,[VFATCsum]
784                 je .vfat_cp_ln
785                 jmp .vfat_abort
786
787 .vfat_ck_ln:            ; Load this line's VFAT CheckSum
788                 mov bl,[gs:si+13]
789                 mov [VFATCsum],bl
790 .vfat_cp_ln:            ; Copy VFAT line
791                 dec al          ; Store the next line we need
792                 mov dx,ax       ; Use DX to store the progress
793                 mov cx,13       ; 13 characters per VFAT DIRENT
794                 cbw             ; AH <- 0
795                 mul cl          ; Offset for DI
796                 add di,ax       ; Increment DI
797                 inc si          ; Align to the real characters
798 .vfat_cp_chr:
799                 gs lodsw        ; Unicode here!!
800                 call ucs2_to_cp ; Convert to local codepage
801                 jnz .vfat_abort ; Use short name if character not on codepage
802                 stosb           ; CAN NOT OVERRIDE es
803                 cmp al,0
804                 jz .vfat_find_next ; Null-terminated string; don't process more
805                 cmp cx,3
806                 je .vfat_adj_add2
807                 cmp cx,9
808                 jne .vfat_adj_add0
809 .vfat_adj_add3: inc si
810 .vfat_adj_add2: inc si
811 .vfat_adj_add1: inc si
812 .vfat_adj_add0:
813                 loop .vfat_cp_chr
814                 cmp dh,1        ; Is this the first round?
815                 jnz .vfat_find_next
816 .vfat_null_term:        ; Need to null-terminate if first line as we rolled over the end
817                 mov al,0
818                 stosb
819
820 .vfat_find_next:        ;Find the next part of the name
821                 pop di
822                 pop si
823                 pop ecx
824                 pop eax
825                 cmp dl,0
826                 jz .vfat_find_info      ; We're done with the name
827                 add si,DIRENT_SIZE
828                 dec cx
829                 jnz .vfat_entry
830                 call nextsector
831                 jnc .vfat_entry                 ; CF is set if we're at end
832                 jmp .fail
833 .vfat_find_info:        ; Fetch next entry for the size/"INode"
834                 add si,DIRENT_SIZE
835                 dec cx
836                 jnz .get_info
837                 call nextsector
838                 jnc .get_info                   ; CF is set if we're at end
839                 jmp .fail
840 .vfat_abort:            ; Something went wrong, skip
841                 pop di
842                 pop si
843                 pop ecx
844                 pop eax
845                 jmp .skip_entry
846
847 .short_entry:
848                 test byte [gs:si+11],8          ; Ignore volume labels //HERE
849                 jnz .skip_entry
850                 mov edx,eax             ;Save current sector
851                 push cx
852                 push si
853                 push di
854                 mov cx,8
855 .short_file:
856                 gs lodsb
857                 cmp al,'.'
858                 jz .short_dot
859 .short_file_loop:
860                 cmp al,' '
861                 jz .short_skip_bs
862                 stosb
863                 loop .short_file_loop
864                 jmp .short_period
865 .short_skip_bs:         ; skip blank spaces in FILENAME (before EXT)
866                 add si,cx
867                 dec si
868 .short_period:
869                 mov al,'.'
870                 stosb
871                 mov cx,3
872 .short_ext:
873                 gs lodsb
874                 cmp al,' '
875                 jz .short_done
876                 stosb
877                 loop .short_ext
878                 jmp .short_done
879 .short_dot:
880                 stosb
881                 gs lodsb
882                 cmp al,' '
883                 jz .short_done
884                 stosb
885 .short_done:
886                 mov al,0        ; Null-terminate the short strings
887                 stosb
888                 pop di
889                 pop si
890                 pop cx
891                 mov eax,edx
892 .get_info:
893                 mov ebx,[gs:si+28]      ; length
894                 mov dl,[gs:si+11]       ; type
895 .next_entry:
896                 add si,DIRENT_SIZE
897                 dec cx
898                 jnz .store_offset
899                 call nextsector
900                 jnc .store_sect                 ; CF is set if we're at end
901                 jmp .fail
902
903 .skip_entry:
904                 add si,DIRENT_SIZE
905                 dec cx
906                 jnz .scanentry
907                 call nextsector
908                 jnc .scanentry                  ; CF is set if we're at end
909                 jmp .fail
910
911 .store_sect:
912                 pop gs
913                 pop fs
914                 pop es
915                 pop si
916                 mov [ds:si+file_sector],eax
917                 mov eax,0       ; Now at beginning of new sector
918                 jmp .success
919
920 .store_offset:
921                 pop gs
922                 pop fs
923                 pop es
924                 pop si          ; cx=num remain; SECTOR_SIZE-(cx*32)=cur pos
925                 shl ecx,DIRENT_SHIFT
926                 mov eax,SECTOR_SIZE
927                 sub eax,ecx
928                 and eax,0ffffh
929
930 .success:
931                 mov [ds:si+file_bytesleft],eax
932                 ; "INode" number = ((CurSector-RootSector)*SECTOR_SIZE + Offset)/DIRENT_SIZE)
933                 mov ecx,eax
934                 mov eax,[ds:si+file_sector]
935                 sub eax,[RootDir]
936                 shl eax,SECTOR_SHIFT
937                 add eax,ecx
938                 shr eax,DIRENT_SHIFT
939                 dec eax
940                 xchg eax,ebx    ; -> EBX=INode, EAX=FileSize
941                 jmp .done
942
943 .fail:
944                 pop gs
945                 pop fs
946                 pop es
947                 pop si
948                 call close_dir
949                 xor eax,eax
950                 stc
951 .done:
952                 pop bp
953                 pop ecx
954 .end:
955                 ret
956
957                 section .bss
958                 alignb 4
959 CurrentDir      resd 1                  ; Current directory
960 PrevDir         resd 1                  ; Last scanned directory
961
962                 section .text
963
964 ;
965 ;
966 ; kaboom2: once everything is loaded, replace the part of kaboom
967 ;          starting with "kaboom.patch" with this part
968
969 kaboom2:
970                 mov si,err_bootfailed
971                 call writestr
972                 cmp byte [kaboom.again+1],18h   ; INT 18h version?
973                 je .int18
974                 call getchar
975                 call vgaclearmode
976                 int 19h                 ; And try once more to boot...
977 .norge:         jmp short .norge        ; If int 19h returned; this is the end
978 .int18:
979                 call vgaclearmode
980                 int 18h
981 .noreg:         jmp short .noreg        ; Nynorsk
982
983 ;
984 ; mangle_name: Mangle a filename pointed to by DS:SI into a buffer pointed
985 ;              to by ES:DI; ends on encountering any whitespace.
986 ;              DI is preserved.
987 ;
988 ;              This verifies that a filename is < FILENAME_MAX characters,
989 ;              doesn't contain whitespace, zero-pads the output buffer,
990 ;              and removes trailing dots and redundant slashes, plus changes
991 ;              backslashes to forward slashes,
992 ;              so "repe cmpsb" can do a compare, and the path-searching routine
993 ;              gets a bit of an easier job.
994 ;
995 ;
996 mangle_name:
997                 push di
998                 push bx
999                 xor ax,ax
1000                 mov cx,FILENAME_MAX-1
1001                 mov bx,di
1002
1003 .mn_loop:
1004                 lodsb
1005                 cmp al,' '                      ; If control or space, end
1006                 jna .mn_end
1007                 cmp al,'\'                      ; Backslash?
1008                 jne .mn_not_bs
1009                 mov al,'/'                      ; Change to forward slash
1010 .mn_not_bs:
1011                 cmp al,ah                       ; Repeated slash?
1012                 je .mn_skip
1013                 xor ah,ah
1014                 cmp al,'/'
1015                 jne .mn_ok
1016                 mov ah,al
1017 .mn_ok          stosb
1018 .mn_skip:       loop .mn_loop
1019 .mn_end:
1020                 cmp bx,di                       ; At the beginning of the buffer?
1021                 jbe .mn_zero
1022                 cmp byte [es:di-1],'.'          ; Terminal dot?
1023                 je .mn_kill
1024                 cmp byte [es:di-1],'/'          ; Terminal slash?
1025                 jne .mn_zero
1026 .mn_kill:       dec di                          ; If so, remove it
1027                 inc cx
1028                 jmp short .mn_end
1029 .mn_zero:
1030                 inc cx                          ; At least one null byte
1031                 xor ax,ax                       ; Zero-fill name
1032                 rep stosb
1033                 pop bx
1034                 pop di
1035                 ret                             ; Done
1036
1037 ;
1038 ; unmangle_name: Does the opposite of mangle_name; converts a DOS-mangled
1039 ;                filename to the conventional representation.  This is needed
1040 ;                for the BOOT_IMAGE= parameter for the kernel.
1041 ;                NOTE: A 13-byte buffer is mandatory, even if the string is
1042 ;                known to be shorter.
1043 ;
1044 ;                DS:SI -> input mangled file name
1045 ;                ES:DI -> output buffer
1046 ;
1047 ;                On return, DI points to the first byte after the output name,
1048 ;                which is set to a null byte.
1049 ;
1050 unmangle_name:  call strcpy
1051                 dec di                          ; Point to final null byte
1052                 ret
1053
1054 ;
1055 ; mangle_dos_name:
1056 ;               Mangle a DOS filename component pointed to by DS:SI
1057 ;               into [MangledBuf]; ends on encountering any whitespace or
1058 ;               slash.
1059 ;
1060 ;               WARNING: saves pointers into the buffer for longname
1061 ;               matches!
1062 ;
1063 ;               Assumes CS == DS == ES.
1064 ;
1065
1066 mangle_dos_name:
1067                 pusha
1068                 mov di,MangledBuf
1069                 mov [NameStart],si
1070
1071                 mov cx,11                       ; # of bytes to write
1072                 mov bx,cp_uppercase             ; Case-conversion table
1073 .loop:
1074                 lodsb
1075                 cmp al,' '                      ; If control or space, end
1076                 jna .end
1077                 cmp al,'/'                      ; Slash, too
1078                 je .end
1079                 cmp al,'.'                      ; Period -> space-fill
1080                 je .is_period
1081                 xlatb                           ; Convert to upper case
1082                 mov ah,cl                       ; If the first byte (only!)...
1083                 cmp ax,0BE5h                    ; ... equals E5 hex ...
1084                 jne .charok
1085                 mov al,05h                      ; ... change it to 05 hex
1086 .charok:        stosb
1087                 loop .loop                      ; Don't continue if too long
1088                 ; Find the end for the benefit of longname search
1089 .find_end:
1090                 lodsb
1091                 cmp al,' '
1092                 jna .end
1093                 cmp al,'/'
1094                 jne .find_end
1095 .end:
1096                 dec si
1097                 sub si,[NameStart]
1098                 mov [NameLen],si
1099                 mov al,' '                      ; Space-fill name
1100                 rep stosb                       ; Doesn't do anything if CX=0
1101                 popa
1102                 ret                             ; Done
1103
1104 .is_period:
1105                 mov al,' '                      ; We need to space-fill
1106 .period_loop:   cmp cx,3                        ; If <= 3 characters left
1107                 jbe .loop                       ; Just ignore it
1108                 stosb                           ; Otherwise, write a space
1109                 loop .period_loop               ; Dec CX and *always* jump
1110
1111                 section .bss
1112                 alignb 2
1113 NameStart       resw 1
1114 NameLen         resw 1
1115 MangledBuf      resb 11
1116
1117                 section .text
1118 ;
1119 ; getfssec_edx: Get multiple sectors from a file
1120 ;
1121 ;       This routine makes sure the subtransfers do not cross a 64K boundary,
1122 ;       and will correct the situation if it does, UNLESS *sectors* cross
1123 ;       64K boundaries.
1124 ;
1125 ;       ES:BX   -> Buffer
1126 ;       EDX     -> Current sector number
1127 ;       CX      -> Sector count (0FFFFh = until end of file)
1128 ;                  Must not exceed the ES segment
1129 ;       Returns EDX=0, CF=1 on EOF (not necessarily error)
1130 ;       All arguments are advanced to reflect data read.
1131 ;
1132 getfssec_edx:
1133                 push ebp
1134                 push eax
1135 .getfragment:
1136                 xor ebp,ebp                     ; Fragment sector count
1137                 push edx                        ; Starting sector pointer
1138 .getseccnt:
1139                 inc bp
1140                 dec cx
1141                 jz .do_read
1142                 xor eax,eax
1143                 mov ax,es
1144                 shl ax,4
1145                 add ax,bx                       ; Now AX = how far into 64K block we are
1146                 not ax                          ; Bytes left in 64K block
1147                 inc eax
1148                 shr eax,SECTOR_SHIFT            ; Sectors left in 64K block
1149                 cmp bp,ax
1150                 jnb .do_read                    ; Unless there is at least 1 more sector room...
1151                 mov eax,edx                     ; Current sector
1152                 inc edx                         ; Predict it's the linearly next sector
1153                 call nextsector
1154                 jc .do_read
1155                 cmp edx,eax                     ; Did it match?
1156                 jz .getseccnt
1157 .do_read:
1158                 pop eax                         ; Starting sector pointer
1159                 call getlinsecsr
1160                 lea eax,[eax+ebp-1]             ; This is the last sector actually read
1161                 shl bp,9
1162                 add bx,bp                       ; Adjust buffer pointer
1163                 call nextsector
1164                 jc .eof
1165                 mov edx,eax
1166                 and cx,cx
1167                 jnz .getfragment
1168 .done:
1169                 pop eax
1170                 pop ebp
1171                 ret
1172 .eof:
1173                 xor edx,edx
1174                 stc
1175                 jmp .done
1176
1177 ;
1178 ; getfssec: Get multiple sectors from a file
1179 ;
1180 ;       Same as above, except SI is a pointer to a open_file_t
1181 ;
1182 ;       ES:BX   -> Buffer
1183 ;       DS:SI   -> Pointer to open_file_t
1184 ;       CX      -> Sector count (0FFFFh = until end of file)
1185 ;                  Must not exceed the ES segment
1186 ;       Returns CF=1 on EOF (not necessarily error)
1187 ;       ECX returns number of bytes read.
1188 ;       All arguments are advanced to reflect data read.
1189 ;
1190 getfssec:
1191                 push edx
1192                 movzx edx,cx
1193                 push edx                ; Zero-extended CX
1194                 cmp edx,[si+file_left]
1195                 jbe .sizeok
1196                 mov edx,[si+file_left]
1197                 mov cx,dx
1198 .sizeok:
1199                 sub [si+file_left],edx
1200                 mov edx,[si+file_sector]
1201                 call getfssec_edx
1202                 mov [si+file_sector],edx
1203                 pop ecx                 ; Sectors requested read
1204                 shl ecx,SECTOR_SHIFT
1205                 cmp ecx,[si+file_bytesleft]
1206                 ja .eof
1207 .noteof:
1208                 sub [si+file_bytesleft],ecx     ; CF <- 0
1209                 pop edx
1210                 ret
1211 .eof:
1212                 mov ecx,[si+file_bytesleft]
1213                 call close_file
1214                 pop edx
1215                 stc
1216                 ret
1217
1218 ;
1219 ; nextcluster: Advance a cluster pointer in EDI to the next cluster
1220 ;              pointed at in the FAT tables.  CF=0 on return if end of file.
1221 ;
1222 nextcluster:
1223                 jmp strict short nextcluster_fat28      ; This gets patched
1224
1225 nextcluster_fat12:
1226                 push eax
1227                 push edx
1228                 push bx
1229                 push cx
1230                 push si
1231                 mov edx,edi
1232                 shr edi,1
1233                 pushf                   ; Save the shifted-out LSB (=CF)
1234                 add edx,edi
1235                 mov eax,edx
1236                 shr eax,9
1237                 call getfatsector
1238                 mov bx,dx
1239                 and bx,1FFh
1240                 mov cl,[gs:si+bx]
1241                 inc edx
1242                 mov eax,edx
1243                 shr eax,9
1244                 call getfatsector
1245                 mov bx,dx
1246                 and bx,1FFh
1247                 mov ch,[gs:si+bx]
1248                 popf
1249                 jnc .even
1250                 shr cx,4
1251 .even:          and cx,0FFFh
1252                 movzx edi,cx
1253                 lea ax,[di-2]
1254                 cmp ax,[Clusters]
1255                 pop si
1256                 pop cx
1257                 pop bx
1258                 pop edx
1259                 pop eax
1260                 ret
1261
1262 ;
1263 ; FAT16 decoding routine.
1264 ;
1265 nextcluster_fat16:
1266                 push eax
1267                 push si
1268                 push bx
1269                 mov eax,edi
1270                 shr eax,SECTOR_SHIFT-1
1271                 call getfatsector
1272                 mov bx,di
1273                 add bx,bx
1274                 and bx,1FEh
1275                 movzx edi,word [gs:si+bx]
1276                 lea ax,[di-2]
1277                 cmp ax,[Clusters]
1278                 pop bx
1279                 pop si
1280                 pop eax
1281                 ret
1282 ;
1283 ; FAT28 ("FAT32") decoding routine.
1284 ;
1285 nextcluster_fat28:
1286                 push eax
1287                 push si
1288                 push bx
1289                 mov eax,edi
1290                 shr eax,SECTOR_SHIFT-2
1291                 call getfatsector
1292                 mov bx,di
1293                 add bx,bx
1294                 add bx,bx
1295                 and bx,1FCh
1296                 mov edi,dword [gs:si+bx]
1297                 and edi,0FFFFFFFh       ; 28 bits only
1298                 lea eax,[edi-2]
1299                 cmp eax,[Clusters]
1300                 pop bx
1301                 pop si
1302                 pop eax
1303                 ret
1304
1305 ;
1306 ; nextsector:   Given a sector in EAX on input, return the next sector
1307 ;               of the same filesystem object, which may be the root
1308 ;               directory or a cluster chain.  Returns  EOF.
1309 ;
1310 ;               Assumes CS == DS.
1311 ;
1312 nextsector:
1313                 push edi
1314                 push edx
1315                 mov edx,[DataArea]
1316                 mov edi,eax
1317                 sub edi,edx
1318                 jae .isdata
1319
1320                 ; Root directory
1321                 inc eax
1322                 cmp eax,edx
1323                 cmc
1324                 jmp .done
1325
1326 .isdata:
1327                 not edi
1328                 test edi,[ClustMask]
1329                 jz .endcluster
1330
1331                 ; It's not the final sector in a cluster
1332                 inc eax
1333                 jmp .done
1334
1335 .endcluster:
1336                 push gs                 ; nextcluster trashes gs
1337                 push cx
1338                 not edi
1339                 mov cl,[ClustShift]
1340                 shr edi,cl
1341                 add edi,2
1342
1343                 ; Now EDI contains the cluster number
1344                 call nextcluster
1345                 cmc
1346                 jc .exit                ; There isn't anything else...
1347
1348                 ; New cluster number now in EDI
1349                 sub edi,2
1350                 shl edi,cl              ; CF <- 0, unless something is very wrong
1351                 lea eax,[edi+edx]
1352 .exit:
1353                 pop cx
1354                 pop gs
1355 .done:
1356                 pop edx
1357                 pop edi
1358                 ret
1359
1360 ;
1361 ; getfatsector: Check for a particular sector (in EAX) in the FAT cache,
1362 ;               and return a pointer in GS:SI, loading it if needed.
1363 ;
1364 ;               Assumes CS == DS.
1365 ;
1366 getfatsector:
1367                 add eax,[FAT]           ; FAT starting address
1368                 jmp getcachesector
1369
1370 ; -----------------------------------------------------------------------------
1371 ;  Common modules
1372 ; -----------------------------------------------------------------------------
1373
1374 %include "getc.inc"             ; getc et al
1375 %include "conio.inc"            ; Console I/O
1376 %include "plaincon.inc"         ; writechr
1377 %include "writestr.inc"         ; String output
1378 %include "writehex.inc"         ; Hexadecimal output
1379 %include "configinit.inc"       ; Initialize configuration
1380 %include "parseconfig.inc"      ; High-level config file handling
1381 %include "parsecmd.inc"         ; Low-level config file handling
1382 %include "bcopy32.inc"          ; 32-bit bcopy
1383 %include "loadhigh.inc"         ; Load a file into high memory
1384 %include "font.inc"             ; VGA font stuff
1385 %include "graphics.inc"         ; VGA graphics
1386 %include "highmem.inc"          ; High memory sizing
1387 %include "strcpy.inc"           ; strcpy()
1388 %include "cache.inc"            ; Metadata disk cache
1389 %include "idle.inc"             ; Idle handling
1390 %include "adv.inc"              ; Auxillary Data Vector
1391 %include "localboot.inc"        ; Disk-based local boot
1392
1393 ; -----------------------------------------------------------------------------
1394 ;  Begin data section
1395 ; -----------------------------------------------------------------------------
1396
1397                 section .data
1398 copyright_str   db ' Copyright (C) 1994-'
1399                 asciidec YEAR
1400                 db ' H. Peter Anvin et al', CR, LF, 0
1401 err_bootfailed  db CR, LF, 'Boot failed: please change disks and press '
1402                 db 'a key to continue.', CR, LF, 0
1403 syslinux_cfg1   db '/boot'                      ; /boot/syslinux/syslinux.cfg
1404 syslinux_cfg2   db '/syslinux'                  ; /syslinux/syslinux.cfg
1405 syslinux_cfg3   db '/'                          ; /syslinux.cfg
1406 config_name     db 'syslinux.cfg', 0            ; syslinux.cfg
1407
1408 ;
1409 ; Config file keyword table
1410 ;
1411 %include "keywords.inc"
1412
1413 ;
1414 ; Extensions to search for (in *forward* order).
1415 ;
1416 exten_table:    db '.cbt'               ; COMBOOT (specific)
1417                 db '.bss'               ; Boot Sector (add superblock)
1418                 db '.bs', 0             ; Boot Sector
1419                 db '.com'               ; COMBOOT (same as DOS)
1420                 db '.c32'               ; COM32
1421 exten_table_end:
1422                 dd 0, 0                 ; Need 8 null bytes here
1423
1424 ;
1425 ; Misc initialized (data) variables
1426 ;
1427 %ifdef debug                            ; This code for debugging only
1428 debug_magic     dw 0D00Dh               ; Debug code sentinel
1429 %endif
1430
1431                 alignz 4
1432 BufSafe         dw trackbufsize/SECTOR_SIZE     ; Clusters we can load into trackbuf
1433 BufSafeBytes    dw trackbufsize         ; = how many bytes?
1434 %ifndef DEPEND
1435 %if ( trackbufsize % SECTOR_SIZE ) != 0
1436 %error trackbufsize must be a multiple of SECTOR_SIZE
1437 %endif
1438 %endif