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