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